summaryrefslogtreecommitdiff
path: root/compiler/GHC/Iface/Ext/Utils.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Iface/Ext/Utils.hs')
-rw-r--r--compiler/GHC/Iface/Ext/Utils.hs27
1 files changed, 27 insertions, 0 deletions
diff --git a/compiler/GHC/Iface/Ext/Utils.hs b/compiler/GHC/Iface/Ext/Utils.hs
index c4c86dd216..0a9150f532 100644
--- a/compiler/GHC/Iface/Ext/Utils.hs
+++ b/compiler/GHC/Iface/Ext/Utils.hs
@@ -25,6 +25,7 @@ import GHC.Core.TyCo.Rep
import GHC.Core.Type
import GHC.Types.Var
import GHC.Types.Var.Env
+import GHC.Parser.Annotation
import GHC.Iface.Ext.Types
@@ -523,6 +524,9 @@ locOnly (RealSrcSpan span _) = do
pure [Node e span []]
locOnly _ = pure []
+mkScopeA :: SrcSpanAnn' ann -> Scope
+mkScopeA l = mkScope (locA l)
+
mkScope :: SrcSpan -> Scope
mkScope (RealSrcSpan sp _) = LocalScope sp
mkScope _ = NoScope
@@ -530,6 +534,12 @@ mkScope _ = NoScope
mkLScope :: Located a -> Scope
mkLScope = mkScope . getLoc
+mkLScopeA :: GenLocated (SrcSpanAnn' a) e -> Scope
+mkLScopeA = mkScope . locA . getLoc
+
+mkLScopeN :: LocatedN a -> Scope
+mkLScopeN = mkScope . getLocA
+
combineScopes :: Scope -> Scope -> Scope
combineScopes ModuleScope _ = ModuleScope
combineScopes _ ModuleScope = ModuleScope
@@ -541,6 +551,14 @@ combineScopes (LocalScope a) (LocalScope b) =
mkSourcedNodeInfo :: NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo org ni = SourcedNodeInfo $ M.singleton org ni
+{-# INLINEABLE makeNodeA #-}
+makeNodeA
+ :: (Monad m, Data a)
+ => a -- ^ helps fill in 'nodeAnnotations' (with 'Data')
+ -> SrcSpanAnn' ann -- ^ return an empty list if this is unhelpful
+ -> ReaderT NodeOrigin m [HieAST b]
+makeNodeA x spn = makeNode x (locA spn)
+
{-# INLINEABLE makeNode #-}
makeNode
:: (Monad m, Data a)
@@ -556,6 +574,15 @@ makeNode x spn = do
cons = mkFastString . show . toConstr $ x
typ = mkFastString . show . typeRepTyCon . typeOf $ x
+{-# INLINEABLE makeTypeNodeA #-}
+makeTypeNodeA
+ :: (Monad m, Data a)
+ => a -- ^ helps fill in 'nodeAnnotations' (with 'Data')
+ -> SrcSpanAnnA -- ^ return an empty list if this is unhelpful
+ -> Type -- ^ type to associate with the node
+ -> ReaderT NodeOrigin m [HieAST Type]
+makeTypeNodeA x spn etyp = makeTypeNode x (locA spn) etyp
+
{-# INLINEABLE makeTypeNode #-}
makeTypeNode
:: (Monad m, Data a)