summaryrefslogtreecommitdiff
path: root/ghc/GHCi/UI/Info.hs
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/GHCi/UI/Info.hs')
-rw-r--r--ghc/GHCi/UI/Info.hs14
1 files changed, 7 insertions, 7 deletions
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index 2bf061f3b5..b07a376482 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -325,7 +325,7 @@ processAllTypeCheckedModule tcm = do
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LHsBind's
getTypeLHsBind :: LHsBind GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
- getTypeLHsBind (dL->L _spn FunBind{fun_id = pid,fun_matches = MG _ _ _})
+ getTypeLHsBind (L _spn FunBind{fun_id = pid,fun_matches = MG _ _ _})
= pure $ Just (Just (unLoc pid),getLoc pid,varType (unLoc pid))
getTypeLHsBind _ = pure Nothing
@@ -337,25 +337,25 @@ processAllTypeCheckedModule tcm = do
return $ fmap (\expr -> (mid, getLoc e, CoreUtils.exprType expr)) mbe
where
mid :: Maybe Id
- mid | HsVar _ (dL->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'
-- | Extract 'Id', 'SrcSpan', and 'Type' for 'LPats's
getTypeLPat :: LPat GhcTc -> m (Maybe (Maybe Id,SrcSpan,Type))
- getTypeLPat (dL->L spn pat) =
+ getTypeLPat (L spn pat) =
pure (Just (getMaybeId pat,spn,hsPatType pat))
where
- getMaybeId (VarPat _ (dL->L _ vid)) = Just vid
+ getMaybeId (VarPat _ (L _ vid)) = Just vid
getMaybeId _ = Nothing
-- | Get ALL source spans in the source.
- listifyAllSpans :: (HasSrcSpan a , Typeable a) => TypecheckedSource -> [a]
+ listifyAllSpans :: Typeable a => TypecheckedSource -> [Located a]
listifyAllSpans = everythingAllSpans (++) [] ([] `mkQ` (\x -> [x | p x]))
where
- p (dL->L spn _) = isGoodSrcSpan spn
+ p (L spn _) = isGoodSrcSpan spn
-- | Variant of @syb@'s @everything@ (which summarises all nodes
-- in top-down, left-to-right order) with a stop-condition on 'NameSet's