summaryrefslogtreecommitdiff
path: root/ghc/GHCi/UI/Info.hs
diff options
context:
space:
mode:
authorKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
committerKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
commit84c2ad99582391005b5e873198b15e9e9eb4f78d (patch)
treecaa8c2f2ec7e97fbb4977263c6817c9af5025cf4 /ghc/GHCi/UI/Info.hs
parent8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 (diff)
parente68b439fe5de61b9a2ca51af472185c62ccb8b46 (diff)
downloadhaskell-wip/T13904.tar.gz
update to current master againwip/T13904
Diffstat (limited to 'ghc/GHCi/UI/Info.hs')
-rw-r--r--ghc/GHCi/UI/Info.hs22
1 files changed, 12 insertions, 10 deletions
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index a114ebff29..0b354f93e7 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
--- | Get information on modules, expreesions, and identifiers
+-- | Get information on modules, expressions, and identifiers
module GHCi.UI.Info
( ModInfo(..)
, SpanInfo(..)
@@ -27,7 +27,7 @@ import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe
import Data.Time
-import Prelude hiding (mod)
+import Prelude hiding (mod,(<>))
import System.Directory
import qualified CoreUtils
@@ -276,7 +276,9 @@ collectInfo ms loaded = do
cacheInvalid name = case M.lookup name ms of
Nothing -> return True
Just mi -> do
- let fp = ml_obj_file (ms_location (modinfoSummary mi))
+ let src_fp = ml_hs_file (ms_location (modinfoSummary mi))
+ obj_fp = ml_obj_file (ms_location (modinfoSummary mi))
+ fp = fromMaybe obj_fp src_fp
last' = modinfoLastUpdate mi
exists <- doesFileExist fp
if exists
@@ -309,7 +311,7 @@ processAllTypeCheckedModule tcm = do
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LHsBind's
getTypeLHsBind :: LHsBind GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
- getTypeLHsBind (L _spn FunBind{fun_id = pid,fun_matches = MG _ _ _typ _})
+ getTypeLHsBind (L _spn FunBind{fun_id = pid,fun_matches = MG _ _ _})
= pure $ Just (Just (unLoc pid),getLoc pid,varType (unLoc pid))
getTypeLHsBind _ = pure Nothing
@@ -321,19 +323,19 @@ processAllTypeCheckedModule tcm = do
return $ fmap (\expr -> (mid, getLoc e, CoreUtils.exprType expr)) mbe
where
mid :: Maybe Id
- mid | HsVar (L _ i) <- unwrapVar (unLoc e) = Just i
- | otherwise = Nothing
+ mid | HsVar _ (L _ i) <- unwrapVar (unLoc e) = Just i
+ | otherwise = Nothing
- unwrapVar (HsWrap _ var) = var
- unwrapVar e' = e'
+ unwrapVar (HsWrap _ _ var) = var
+ unwrapVar e' = e'
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LPats's
getTypeLPat :: LPat GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
getTypeLPat (L spn pat) =
pure (Just (getMaybeId pat,spn,hsPatType pat))
where
- getMaybeId (VarPat (L _ vid)) = Just vid
- getMaybeId _ = Nothing
+ getMaybeId (VarPat _ (L _ vid)) = Just vid
+ getMaybeId _ = Nothing
-- | Get ALL source spans in the source.
listifyAllSpans :: Typeable a => TypecheckedSource -> [Located a]