diff options
author | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2019-11-20 15:44:49 +0300 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2019-11-30 02:58:34 -0500 |
commit | 5aba5d3218330f8ce127aa7767efcbb6f63a2db1 (patch) | |
tree | d11ea424fedf51668f5d9f14c972e6f1dca6693a /ghc/GHCi/UI | |
parent | 316f24319e151446c83cbb0f2997a73e19fe4aa3 (diff) | |
download | haskell-5aba5d3218330f8ce127aa7767efcbb6f63a2db1.tar.gz |
Remove HasSrcSpan (#17494)
Metric Decrease:
haddock.compiler
Diffstat (limited to 'ghc/GHCi/UI')
-rw-r--r-- | ghc/GHCi/UI/Info.hs | 14 |
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 |