{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TupleSections #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Iface.Ext.Ast ( mkHieFile, mkHieFileWithSource, getCompressedAsts, enrichHie) where
import GHC.Utils.Outputable(ppr)
import GHC.Prelude
import GHC.Types.Avail ( Avails )
import GHC.Data.Bag ( Bag, bagToList )
import GHC.Types.Basic
import GHC.Data.BooleanFormula
import GHC.Core.Class ( FunDep, className, classSCSelIds )
import GHC.Core.Utils ( exprType )
import GHC.Core.ConLike ( conLikeName, ConLike(RealDataCon) )
import GHC.Core.TyCon ( TyCon, tyConClass_maybe )
import GHC.Core.FVs
import GHC.Core.DataCon ( dataConNonlinearType )
import GHC.HsToCore ( deSugarExpr )
import GHC.Types.FieldLabel
import GHC.Hs
import GHC.Driver.Types
import GHC.Unit.Module ( ModuleName, ml_hs_file )
import GHC.Utils.Monad ( concatMapM, liftIO )
import GHC.Types.Id ( isDataConId_maybe )
import GHC.Types.Name ( Name, nameSrcSpan, nameUnique )
import GHC.Types.Name.Env ( NameEnv, emptyNameEnv, extendNameEnv, lookupNameEnv )
import GHC.Types.SrcLoc
import GHC.Tc.Utils.Zonk ( hsLitType, hsPatType )
import GHC.Core.Type ( mkVisFunTys, Type )
import GHC.Core.Predicate
import GHC.Core.InstEnv
import GHC.Builtin.Types ( mkListTy, mkSumTy )
import GHC.Tc.Types
import GHC.Tc.Types.Evidence
import GHC.Types.Var ( Id, Var, EvId, varName, setVarName, varType, varUnique )
import GHC.Types.Var.Env
import GHC.Types.Unique
import GHC.Iface.Make ( mkIfaceExports )
import GHC.Utils.Panic
import GHC.Data.Maybe
import GHC.Data.FastString
import GHC.Iface.Ext.Types
import GHC.Iface.Ext.Utils
import qualified Data.Array as A
import qualified Data.ByteString as BS
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Data ( Data, Typeable )
import Data.List ( foldl1' )
import Control.Monad ( forM_ )
import Control.Monad.Trans.State.Strict
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Class ( lift )
type RenamedSource = ( HsGroup GhcRn, [LImportDecl GhcRn]
, Maybe [(LIE GhcRn, Avails)]
, Maybe LHsDocString )
type TypecheckedSource = LHsBinds GhcTc
type VarMap a = DVarEnv (Var,a)
data HieState = HieState
{ HieState -> NameEnv Id
name_remapping :: NameEnv Id
, HieState -> VarMap (Set ContextInfo)
unlocated_ev_binds :: VarMap (S.Set ContextInfo)
}
addUnlocatedEvBind :: Var -> ContextInfo -> HieM ()
addUnlocatedEvBind :: Id -> ContextInfo -> HieM ()
addUnlocatedEvBind Id
var ContextInfo
ci = do
let go :: (a, Set a) -> (a, Set a) -> (a, Set a)
go (a
a,Set a
b) (a
_,Set a
c) = (a
a,Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
S.union Set a
b Set a
c)
StateT HieState Hsc () -> HieM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT HieState Hsc () -> HieM ())
-> StateT HieState Hsc () -> HieM ()
forall a b. (a -> b) -> a -> b
$ (HieState -> HieState) -> StateT HieState Hsc ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify' ((HieState -> HieState) -> StateT HieState Hsc ())
-> (HieState -> HieState) -> StateT HieState Hsc ()
forall a b. (a -> b) -> a -> b
$ \HieState
s ->
HieState
s { unlocated_ev_binds :: VarMap (Set ContextInfo)
unlocated_ev_binds =
((Id, Set ContextInfo)
-> (Id, Set ContextInfo) -> (Id, Set ContextInfo))
-> VarMap (Set ContextInfo)
-> Id
-> (Id, Set ContextInfo)
-> VarMap (Set ContextInfo)
forall a. (a -> a -> a) -> DVarEnv a -> Id -> a -> DVarEnv a
extendDVarEnv_C (Id, Set ContextInfo)
-> (Id, Set ContextInfo) -> (Id, Set ContextInfo)
forall {a} {a} {a}. Ord a => (a, Set a) -> (a, Set a) -> (a, Set a)
go (HieState -> VarMap (Set ContextInfo)
unlocated_ev_binds HieState
s)
Id
var (Id
var,ContextInfo -> Set ContextInfo
forall a. a -> Set a
S.singleton ContextInfo
ci)
}
getUnlocatedEvBinds :: FastString -> HieM (NodeIdentifiers Type,[HieAST Type])
getUnlocatedEvBinds :: FastString -> HieM (NodeIdentifiers Type, [HieAST Type])
getUnlocatedEvBinds FastString
file = do
VarMap (Set ContextInfo)
binds <- StateT HieState Hsc (VarMap (Set ContextInfo))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (VarMap (Set ContextInfo))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT HieState Hsc (VarMap (Set ContextInfo))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (VarMap (Set ContextInfo)))
-> StateT HieState Hsc (VarMap (Set ContextInfo))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (VarMap (Set ContextInfo))
forall a b. (a -> b) -> a -> b
$ (HieState -> VarMap (Set ContextInfo))
-> StateT HieState Hsc (VarMap (Set ContextInfo))
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets HieState -> VarMap (Set ContextInfo)
unlocated_ev_binds
NodeOrigin
org <- ReaderT NodeOrigin (StateT HieState Hsc) NodeOrigin
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
let elts :: [(Id, Set ContextInfo)]
elts = VarMap (Set ContextInfo) -> [(Id, Set ContextInfo)]
forall a. DVarEnv a -> [a]
dVarEnvElts VarMap (Set ContextInfo)
binds
mkNodeInfo :: (Id, Set ContextInfo) -> (Either a Name, IdentifierDetails Type)
mkNodeInfo (Id
n,Set ContextInfo
ci) = (Name -> Either a Name
forall a b. b -> Either a b
Right (Id -> Name
varName Id
n), Maybe Type -> Set ContextInfo -> IdentifierDetails Type
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails (Type -> Maybe Type
forall a. a -> Maybe a
Just (Type -> Maybe Type) -> Type -> Maybe Type
forall a b. (a -> b) -> a -> b
$ Id -> Type
varType Id
n) Set ContextInfo
ci)
go :: (Id, Set ContextInfo)
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
go e :: (Id, Set ContextInfo)
e@(Id
v,Set ContextInfo
_) ([(Either ModuleName Name, IdentifierDetails Type)]
xs,[HieAST Type]
ys) = case Name -> SrcSpan
nameSrcSpan (Name -> SrcSpan) -> Name -> SrcSpan
forall a b. (a -> b) -> a -> b
$ Id -> Name
varName Id
v of
RealSrcSpan Span
spn Maybe BufSpan
_
| Span -> FastString
srcSpanFile Span
spn FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== FastString
file ->
let node :: HieAST Type
node = SourcedNodeInfo Type -> Span -> [HieAST Type] -> HieAST Type
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node (NodeOrigin -> NodeInfo Type -> SourcedNodeInfo Type
forall a. NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo NodeOrigin
org NodeInfo Type
ni) Span
spn []
ni :: NodeInfo Type
ni = Set (FastString, FastString)
-> [Type] -> NodeIdentifiers Type -> NodeInfo Type
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo Set (FastString, FastString)
forall a. Monoid a => a
mempty [] (NodeIdentifiers Type -> NodeInfo Type)
-> NodeIdentifiers Type -> NodeInfo Type
forall a b. (a -> b) -> a -> b
$ [(Either ModuleName Name, IdentifierDetails Type)]
-> NodeIdentifiers Type
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Id, Set ContextInfo)
-> (Either ModuleName Name, IdentifierDetails Type)
forall {a}.
(Id, Set ContextInfo) -> (Either a Name, IdentifierDetails Type)
mkNodeInfo (Id, Set ContextInfo)
e]
in ([(Either ModuleName Name, IdentifierDetails Type)]
xs,HieAST Type
nodeHieAST Type -> [HieAST Type] -> [HieAST Type]
forall a. a -> [a] -> [a]
:[HieAST Type]
ys)
SrcSpan
_ -> ((Id, Set ContextInfo)
-> (Either ModuleName Name, IdentifierDetails Type)
forall {a}.
(Id, Set ContextInfo) -> (Either a Name, IdentifierDetails Type)
mkNodeInfo (Id, Set ContextInfo)
e (Either ModuleName Name, IdentifierDetails Type)
-> [(Either ModuleName Name, IdentifierDetails Type)]
-> [(Either ModuleName Name, IdentifierDetails Type)]
forall a. a -> [a] -> [a]
: [(Either ModuleName Name, IdentifierDetails Type)]
xs,[HieAST Type]
ys)
([(Either ModuleName Name, IdentifierDetails Type)]
nis,[HieAST Type]
asts) = ((Id, Set ContextInfo)
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type]))
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
-> [(Id, Set ContextInfo)]
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Id, Set ContextInfo)
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
-> ([(Either ModuleName Name, IdentifierDetails Type)],
[HieAST Type])
go ([],[]) [(Id, Set ContextInfo)]
elts
(NodeIdentifiers Type, [HieAST Type])
-> HieM (NodeIdentifiers Type, [HieAST Type])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((NodeIdentifiers Type, [HieAST Type])
-> HieM (NodeIdentifiers Type, [HieAST Type]))
-> (NodeIdentifiers Type, [HieAST Type])
-> HieM (NodeIdentifiers Type, [HieAST Type])
forall a b. (a -> b) -> a -> b
$ ([(Either ModuleName Name, IdentifierDetails Type)]
-> NodeIdentifiers Type
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Either ModuleName Name, IdentifierDetails Type)]
nis, [HieAST Type]
asts)
initState :: HieState
initState :: HieState
initState = NameEnv Id -> VarMap (Set ContextInfo) -> HieState
HieState NameEnv Id
forall a. NameEnv a
emptyNameEnv VarMap (Set ContextInfo)
forall a. DVarEnv a
emptyDVarEnv
class ModifyState a where
addSubstitution :: a -> a -> HieState -> HieState
instance ModifyState Name where
addSubstitution :: Name -> Name -> HieState -> HieState
addSubstitution Name
_ Name
_ HieState
hs = HieState
hs
instance ModifyState Id where
addSubstitution :: Id -> Id -> HieState -> HieState
addSubstitution Id
mono Id
poly HieState
hs =
HieState
hs{name_remapping :: NameEnv Id
name_remapping = NameEnv Id -> Name -> Id -> NameEnv Id
forall a. NameEnv a -> Name -> a -> NameEnv a
extendNameEnv (HieState -> NameEnv Id
name_remapping HieState
hs) (Id -> Name
varName Id
mono) Id
poly}
modifyState :: ModifyState (IdP p) => [ABExport p] -> HieState -> HieState
modifyState :: forall p.
ModifyState (IdP p) =>
[ABExport p] -> HieState -> HieState
modifyState = (ABExport p -> (HieState -> HieState) -> HieState -> HieState)
-> (HieState -> HieState) -> [ABExport p] -> HieState -> HieState
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ABExport p -> (HieState -> HieState) -> HieState -> HieState
forall {p} {a}.
ModifyState (IdP p) =>
ABExport p -> (a -> HieState) -> a -> HieState
go HieState -> HieState
forall a. a -> a
id
where
go :: ABExport p -> (a -> HieState) -> a -> HieState
go ABE{abe_poly :: forall p. ABExport p -> IdP p
abe_poly=IdP p
poly,abe_mono :: forall p. ABExport p -> IdP p
abe_mono=IdP p
mono} a -> HieState
f
= IdP p -> IdP p -> HieState -> HieState
forall a. ModifyState a => a -> a -> HieState -> HieState
addSubstitution IdP p
mono IdP p
poly (HieState -> HieState) -> (a -> HieState) -> a -> HieState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> HieState
f
go ABExport p
_ a -> HieState
f = a -> HieState
f
type HieM = ReaderT NodeOrigin (StateT HieState Hsc)
mkHieFile :: ModSummary
-> TcGblEnv
-> RenamedSource -> Hsc HieFile
mkHieFile :: ModSummary -> TcGblEnv -> RenamedSource -> Hsc HieFile
mkHieFile ModSummary
ms TcGblEnv
ts RenamedSource
rs = do
let src_file :: FilePath
src_file = FilePath -> Maybe FilePath -> FilePath
forall a. HasCallStack => FilePath -> Maybe a -> a
expectJust FilePath
"mkHieFile" (ModLocation -> Maybe FilePath
ml_hs_file (ModLocation -> Maybe FilePath) -> ModLocation -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
ms)
ByteString
src <- IO ByteString -> Hsc ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> Hsc ByteString)
-> IO ByteString -> Hsc ByteString
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ByteString
BS.readFile FilePath
src_file
FilePath
-> ByteString
-> ModSummary
-> TcGblEnv
-> RenamedSource
-> Hsc HieFile
mkHieFileWithSource FilePath
src_file ByteString
src ModSummary
ms TcGblEnv
ts RenamedSource
rs
mkHieFileWithSource :: FilePath
-> BS.ByteString
-> ModSummary
-> TcGblEnv
-> RenamedSource -> Hsc HieFile
mkHieFileWithSource :: FilePath
-> ByteString
-> ModSummary
-> TcGblEnv
-> RenamedSource
-> Hsc HieFile
mkHieFileWithSource FilePath
src_file ByteString
src ModSummary
ms TcGblEnv
ts RenamedSource
rs = do
let tc_binds :: LHsBinds GhcTc
tc_binds = TcGblEnv -> LHsBinds GhcTc
tcg_binds TcGblEnv
ts
top_ev_binds :: Bag EvBind
top_ev_binds = TcGblEnv -> Bag EvBind
tcg_ev_binds TcGblEnv
ts
insts :: [ClsInst]
insts = TcGblEnv -> [ClsInst]
tcg_insts TcGblEnv
ts
tcs :: [TyCon]
tcs = TcGblEnv -> [TyCon]
tcg_tcs TcGblEnv
ts
(HieASTs TypeIndex
asts', Array TypeIndex HieTypeFlat
arr) <- LHsBinds GhcTc
-> RenamedSource
-> Bag EvBind
-> [ClsInst]
-> [TyCon]
-> Hsc (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
getCompressedAsts LHsBinds GhcTc
tc_binds RenamedSource
rs Bag EvBind
top_ev_binds [ClsInst]
insts [TyCon]
tcs
HieFile -> Hsc HieFile
forall (m :: * -> *) a. Monad m => a -> m a
return (HieFile -> Hsc HieFile) -> HieFile -> Hsc HieFile
forall a b. (a -> b) -> a -> b
$ HieFile :: FilePath
-> Module
-> Array TypeIndex HieTypeFlat
-> HieASTs TypeIndex
-> [AvailInfo]
-> ByteString
-> HieFile
HieFile
{ hie_hs_file :: FilePath
hie_hs_file = FilePath
src_file
, hie_module :: Module
hie_module = ModSummary -> Module
ms_mod ModSummary
ms
, hie_types :: Array TypeIndex HieTypeFlat
hie_types = Array TypeIndex HieTypeFlat
arr
, hie_asts :: HieASTs TypeIndex
hie_asts = HieASTs TypeIndex
asts'
, hie_exports :: [AvailInfo]
hie_exports = [AvailInfo] -> [AvailInfo]
mkIfaceExports (TcGblEnv -> [AvailInfo]
tcg_exports TcGblEnv
ts)
, hie_hs_src :: ByteString
hie_hs_src = ByteString
src
}
getCompressedAsts :: TypecheckedSource -> RenamedSource -> Bag EvBind -> [ClsInst] -> [TyCon]
-> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
getCompressedAsts :: LHsBinds GhcTc
-> RenamedSource
-> Bag EvBind
-> [ClsInst]
-> [TyCon]
-> Hsc (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
getCompressedAsts LHsBinds GhcTc
ts RenamedSource
rs Bag EvBind
top_ev_binds [ClsInst]
insts [TyCon]
tcs = do
HieASTs Type
asts <- LHsBinds GhcTc
-> RenamedSource
-> Bag EvBind
-> [ClsInst]
-> [TyCon]
-> Hsc (HieASTs Type)
enrichHie LHsBinds GhcTc
ts RenamedSource
rs Bag EvBind
top_ev_binds [ClsInst]
insts [TyCon]
tcs
(HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
-> Hsc (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
forall (m :: * -> *) a. Monad m => a -> m a
return ((HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
-> Hsc (HieASTs TypeIndex, Array TypeIndex HieTypeFlat))
-> (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
-> Hsc (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
forall a b. (a -> b) -> a -> b
$ HieASTs Type -> (HieASTs TypeIndex, Array TypeIndex HieTypeFlat)
compressTypes HieASTs Type
asts
enrichHie :: TypecheckedSource -> RenamedSource -> Bag EvBind -> [ClsInst] -> [TyCon]
-> Hsc (HieASTs Type)
enrichHie :: LHsBinds GhcTc
-> RenamedSource
-> Bag EvBind
-> [ClsInst]
-> [TyCon]
-> Hsc (HieASTs Type)
enrichHie LHsBinds GhcTc
ts (HsGroup GhcRn
hsGrp, [GenLocated SrcSpan (ImportDecl GhcRn)]
imports, Maybe [(LIE GhcRn, [AvailInfo])]
exports, Maybe LHsDocString
_) Bag EvBind
ev_bs [ClsInst]
insts [TyCon]
tcs =
(StateT HieState Hsc (HieASTs Type)
-> HieState -> Hsc (HieASTs Type))
-> HieState
-> StateT HieState Hsc (HieASTs Type)
-> Hsc (HieASTs Type)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT HieState Hsc (HieASTs Type)
-> HieState -> Hsc (HieASTs Type)
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT HieState
initState (StateT HieState Hsc (HieASTs Type) -> Hsc (HieASTs Type))
-> StateT HieState Hsc (HieASTs Type) -> Hsc (HieASTs Type)
forall a b. (a -> b) -> a -> b
$ (ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
-> NodeOrigin -> StateT HieState Hsc (HieASTs Type))
-> NodeOrigin
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
-> StateT HieState Hsc (HieASTs Type)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
-> NodeOrigin -> StateT HieState Hsc (HieASTs Type)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT NodeOrigin
SourceInfo (ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
-> StateT HieState Hsc (HieASTs Type))
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
-> StateT HieState Hsc (HieASTs Type)
forall a b. (a -> b) -> a -> b
$ do
[HieAST Type]
tasts <- Bag (BindContext (LHsBindLR GhcTc GhcTc)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Bag (BindContext (LHsBindLR GhcTc GhcTc)) -> HieM [HieAST Type])
-> Bag (BindContext (LHsBindLR GhcTc GhcTc)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsBindLR GhcTc GhcTc -> BindContext (LHsBindLR GhcTc GhcTc))
-> LHsBinds GhcTc -> Bag (BindContext (LHsBindLR GhcTc GhcTc))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BindType
-> Scope
-> LHsBindLR GhcTc GhcTc
-> BindContext (LHsBindLR GhcTc GhcTc)
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
RegularBind Scope
ModuleScope) LHsBinds GhcTc
ts
[HieAST Type]
rasts <- HsGroup GhcRn -> HieM [HieAST Type]
forall {p}.
(ToHie (GenLocated SrcSpan (SpliceDecl p)),
ToHie (GenLocated SrcSpan (DerivDecl p)),
ToHie (GenLocated SrcSpan (FixitySig p)),
ToHie (GenLocated SrcSpan (DefaultDecl p)),
ToHie (GenLocated SrcSpan (ForeignDecl p)),
ToHie (GenLocated SrcSpan (WarnDecls p)),
ToHie (GenLocated SrcSpan (AnnDecl p)),
ToHie (GenLocated SrcSpan (RuleDecls p)),
ToHie (RScoped (HsValBinds p)), ToHie (TyClGroup p)) =>
HsGroup p -> HieM [HieAST Type]
processGrp HsGroup GhcRn
hsGrp
[HieAST Type]
imps <- [GenLocated SrcSpan (ImportDecl GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (ImportDecl GhcRn)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (ImportDecl GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpan (ImportDecl GhcRn) -> Bool)
-> [GenLocated SrcSpan (ImportDecl GhcRn)]
-> [GenLocated SrcSpan (ImportDecl GhcRn)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (GenLocated SrcSpan (ImportDecl GhcRn) -> Bool)
-> GenLocated SrcSpan (ImportDecl GhcRn)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportDecl GhcRn -> Bool
forall pass. ImportDecl pass -> Bool
ideclImplicit (ImportDecl GhcRn -> Bool)
-> (GenLocated SrcSpan (ImportDecl GhcRn) -> ImportDecl GhcRn)
-> GenLocated SrcSpan (ImportDecl GhcRn)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpan (ImportDecl GhcRn) -> ImportDecl GhcRn
forall l e. GenLocated l e -> e
unLoc) [GenLocated SrcSpan (ImportDecl GhcRn)]
imports
[HieAST Type]
exps <- Maybe [IEContext (LIE GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe [IEContext (LIE GhcRn)] -> HieM [HieAST Type])
-> Maybe [IEContext (LIE GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ([(LIE GhcRn, [AvailInfo])] -> [IEContext (LIE GhcRn)])
-> Maybe [(LIE GhcRn, [AvailInfo])]
-> Maybe [IEContext (LIE GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((LIE GhcRn, [AvailInfo]) -> IEContext (LIE GhcRn))
-> [(LIE GhcRn, [AvailInfo])] -> [IEContext (LIE GhcRn)]
forall a b. (a -> b) -> [a] -> [b]
map (((LIE GhcRn, [AvailInfo]) -> IEContext (LIE GhcRn))
-> [(LIE GhcRn, [AvailInfo])] -> [IEContext (LIE GhcRn)])
-> ((LIE GhcRn, [AvailInfo]) -> IEContext (LIE GhcRn))
-> [(LIE GhcRn, [AvailInfo])]
-> [IEContext (LIE GhcRn)]
forall a b. (a -> b) -> a -> b
$ IEType -> LIE GhcRn -> IEContext (LIE GhcRn)
forall a. IEType -> a -> IEContext a
IEC IEType
Export (LIE GhcRn -> IEContext (LIE GhcRn))
-> ((LIE GhcRn, [AvailInfo]) -> LIE GhcRn)
-> (LIE GhcRn, [AvailInfo])
-> IEContext (LIE GhcRn)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LIE GhcRn, [AvailInfo]) -> LIE GhcRn
forall a b. (a, b) -> a
fst) Maybe [(LIE GhcRn, [AvailInfo])]
exports
[ClsInst] -> (ClsInst -> HieM ()) -> HieM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [ClsInst]
insts ((ClsInst -> HieM ()) -> HieM ())
-> (ClsInst -> HieM ()) -> HieM ()
forall a b. (a -> b) -> a -> b
$ \ClsInst
i ->
Id -> ContextInfo -> HieM ()
addUnlocatedEvBind (ClsInst -> Id
is_dfun ClsInst
i) (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind (Bool -> Name -> EvVarSource
EvInstBind Bool
False (ClsInst -> Name
is_cls_nm ClsInst
i)) Scope
ModuleScope Maybe Span
forall a. Maybe a
Nothing)
[TyCon] -> (TyCon -> HieM ()) -> HieM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [TyCon]
tcs ((TyCon -> HieM ()) -> HieM ()) -> (TyCon -> HieM ()) -> HieM ()
forall a b. (a -> b) -> a -> b
$ \TyCon
tc ->
case TyCon -> Maybe Class
tyConClass_maybe TyCon
tc of
Maybe Class
Nothing -> () -> HieM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Class
c -> [Id] -> (Id -> HieM ()) -> HieM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Class -> [Id]
classSCSelIds Class
c) ((Id -> HieM ()) -> HieM ()) -> (Id -> HieM ()) -> HieM ()
forall a b. (a -> b) -> a -> b
$ \Id
v ->
Id -> ContextInfo -> HieM ()
addUnlocatedEvBind Id
v (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind (Bool -> Name -> EvVarSource
EvInstBind Bool
True (Class -> Name
className Class
c)) Scope
ModuleScope Maybe Span
forall a. Maybe a
Nothing)
let spanFile :: FastString -> [HieAST a] -> Span
spanFile FastString
file [HieAST a]
children = case [HieAST a]
children of
[] -> RealSrcLoc -> Span
realSrcLocSpan (FastString -> TypeIndex -> TypeIndex -> RealSrcLoc
mkRealSrcLoc FastString
file TypeIndex
1 TypeIndex
1)
[HieAST a]
_ -> RealSrcLoc -> RealSrcLoc -> Span
mkRealSrcSpan (Span -> RealSrcLoc
realSrcSpanStart (Span -> RealSrcLoc) -> Span -> RealSrcLoc
forall a b. (a -> b) -> a -> b
$ HieAST a -> Span
forall a. HieAST a -> Span
nodeSpan (HieAST a -> Span) -> HieAST a -> Span
forall a b. (a -> b) -> a -> b
$ [HieAST a] -> HieAST a
forall a. [a] -> a
head [HieAST a]
children)
(Span -> RealSrcLoc
realSrcSpanEnd (Span -> RealSrcLoc) -> Span -> RealSrcLoc
forall a b. (a -> b) -> a -> b
$ HieAST a -> Span
forall a. HieAST a -> Span
nodeSpan (HieAST a -> Span) -> HieAST a -> Span
forall a b. (a -> b) -> a -> b
$ [HieAST a] -> HieAST a
forall a. [a] -> a
last [HieAST a]
children)
flat_asts :: [HieAST Type]
flat_asts = [[HieAST Type]] -> [HieAST Type]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [HieAST Type]
tasts
, [HieAST Type]
rasts
, [HieAST Type]
imps
, [HieAST Type]
exps
]
modulify :: FastString
-> [HieAST Type]
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type)
modulify FastString
file [HieAST Type]
xs' = do
[HieAST Type]
top_ev_asts <-
EvBindContext (GenLocated SrcSpan TcEvBinds) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type])
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> Maybe Span
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a. Scope -> Maybe Span -> a -> EvBindContext a
EvBindContext Scope
ModuleScope Maybe Span
forall a. Maybe a
Nothing
(GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds))
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall l e. l -> e -> GenLocated l e
L (Span -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> Span
realSrcLocSpan (RealSrcLoc -> Span) -> RealSrcLoc -> Span
forall a b. (a -> b) -> a -> b
$ FastString -> TypeIndex -> TypeIndex -> RealSrcLoc
mkRealSrcLoc FastString
file TypeIndex
1 TypeIndex
1) Maybe BufSpan
forall a. Maybe a
Nothing)
(TcEvBinds -> GenLocated SrcSpan TcEvBinds)
-> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall a b. (a -> b) -> a -> b
$ Bag EvBind -> TcEvBinds
EvBinds Bag EvBind
ev_bs
(NodeIdentifiers Type
uloc_evs,[HieAST Type]
more_ev_asts) <- FastString -> HieM (NodeIdentifiers Type, [HieAST Type])
getUnlocatedEvBinds FastString
file
let xs :: [HieAST Type]
xs = [HieAST Type] -> [HieAST Type]
mergeSortAsts ([HieAST Type] -> [HieAST Type]) -> [HieAST Type] -> [HieAST Type]
forall a b. (a -> b) -> a -> b
$ [HieAST Type]
xs' [HieAST Type] -> [HieAST Type] -> [HieAST Type]
forall a. [a] -> [a] -> [a]
++ [HieAST Type]
top_ev_asts [HieAST Type] -> [HieAST Type] -> [HieAST Type]
forall a. [a] -> [a] -> [a]
++ [HieAST Type]
more_ev_asts
span :: Span
span = FastString -> [HieAST Type] -> Span
forall {a}. FastString -> [HieAST a] -> Span
spanFile FastString
file [HieAST Type]
xs
moduleInfo :: SourcedNodeInfo Type
moduleInfo = Map NodeOrigin (NodeInfo Type) -> SourcedNodeInfo Type
forall a. Map NodeOrigin (NodeInfo a) -> SourcedNodeInfo a
SourcedNodeInfo
(Map NodeOrigin (NodeInfo Type) -> SourcedNodeInfo Type)
-> Map NodeOrigin (NodeInfo Type) -> SourcedNodeInfo Type
forall a b. (a -> b) -> a -> b
$ NodeOrigin -> NodeInfo Type -> Map NodeOrigin (NodeInfo Type)
forall k a. k -> a -> Map k a
M.singleton NodeOrigin
SourceInfo
(NodeInfo Type -> Map NodeOrigin (NodeInfo Type))
-> NodeInfo Type -> Map NodeOrigin (NodeInfo Type)
forall a b. (a -> b) -> a -> b
$ (FastString -> FastString -> NodeInfo Type
forall a. FastString -> FastString -> NodeInfo a
simpleNodeInfo FastString
"Module" FastString
"Module")
{nodeIdentifiers :: NodeIdentifiers Type
nodeIdentifiers = NodeIdentifiers Type
uloc_evs}
moduleNode :: HieAST Type
moduleNode = SourcedNodeInfo Type -> Span -> [HieAST Type] -> HieAST Type
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node SourcedNodeInfo Type
moduleInfo Span
span []
case [HieAST Type] -> [HieAST Type]
mergeSortAsts ([HieAST Type] -> [HieAST Type]) -> [HieAST Type] -> [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HieAST Type
moduleNode HieAST Type -> [HieAST Type] -> [HieAST Type]
forall a. a -> [a] -> [a]
: [HieAST Type]
xs of
[HieAST Type
x] -> HieAST Type
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type)
forall (m :: * -> *) a. Monad m => a -> m a
return HieAST Type
x
[HieAST Type]
xs -> FilePath
-> SDoc -> ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type)
forall a. FilePath -> SDoc -> a
panicDoc FilePath
"enrichHie: mergeSortAsts returned more than one result" ([Span] -> SDoc
forall a. Outputable a => a -> SDoc
ppr ([Span] -> SDoc) -> [Span] -> SDoc
forall a b. (a -> b) -> a -> b
$ (HieAST Type -> Span) -> [HieAST Type] -> [Span]
forall a b. (a -> b) -> [a] -> [b]
map HieAST Type -> Span
forall a. HieAST a -> Span
nodeSpan [HieAST Type]
xs)
Map FastString (HieAST Type)
asts' <- Map
FastString (ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Map FastString (HieAST Type))
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
(Map
FastString (ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Map FastString (HieAST Type)))
-> Map
FastString (ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Map FastString (HieAST Type))
forall a b. (a -> b) -> a -> b
$ (FastString
-> [HieAST Type]
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
-> Map FastString [HieAST Type]
-> Map
FastString (ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey FastString
-> [HieAST Type]
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type)
modulify
(Map FastString [HieAST Type]
-> Map
FastString
(ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type)))
-> Map FastString [HieAST Type]
-> Map
FastString (ReaderT NodeOrigin (StateT HieState Hsc) (HieAST Type))
forall a b. (a -> b) -> a -> b
$ ([HieAST Type] -> [HieAST Type] -> [HieAST Type])
-> [(FastString, [HieAST Type])] -> Map FastString [HieAST Type]
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
M.fromListWith [HieAST Type] -> [HieAST Type] -> [HieAST Type]
forall a. [a] -> [a] -> [a]
(++)
([(FastString, [HieAST Type])] -> Map FastString [HieAST Type])
-> [(FastString, [HieAST Type])] -> Map FastString [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (HieAST Type -> (FastString, [HieAST Type]))
-> [HieAST Type] -> [(FastString, [HieAST Type])]
forall a b. (a -> b) -> [a] -> [b]
map (\HieAST Type
x -> (Span -> FastString
srcSpanFile (HieAST Type -> Span
forall a. HieAST a -> Span
nodeSpan HieAST Type
x),[HieAST Type
x])) [HieAST Type]
flat_asts
let asts :: HieASTs Type
asts = Map FastString (HieAST Type) -> HieASTs Type
forall a. Map FastString (HieAST a) -> HieASTs a
HieASTs (Map FastString (HieAST Type) -> HieASTs Type)
-> Map FastString (HieAST Type) -> HieASTs Type
forall a b. (a -> b) -> a -> b
$ Map FastString (HieAST Type) -> Map FastString (HieAST Type)
forall a. Map FastString (HieAST a) -> Map FastString (HieAST a)
resolveTyVarScopes Map FastString (HieAST Type)
asts'
HieASTs Type
-> ReaderT NodeOrigin (StateT HieState Hsc) (HieASTs Type)
forall (m :: * -> *) a. Monad m => a -> m a
return HieASTs Type
asts
where
processGrp :: HsGroup p -> HieM [HieAST Type]
processGrp HsGroup p
grp = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ RScoped (HsValBinds p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (HsValBinds p) -> HieM [HieAST Type])
-> RScoped (HsValBinds p) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (HsValBinds p -> RScoped (HsValBinds p))
-> (HsGroup p -> HsValBinds p)
-> HsGroup p
-> RScoped (HsValBinds p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Scope -> HsValBinds p -> RScoped (HsValBinds p)
forall a. Scope -> a -> RScoped a
RS Scope
ModuleScope ) HsGroup p -> HsValBinds p
forall p. HsGroup p -> HsValBinds p
hs_valds HsGroup p
grp
, [GenLocated SrcSpan (SpliceDecl p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (SpliceDecl p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (SpliceDecl p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (SpliceDecl p)]
forall p. HsGroup p -> [LSpliceDecl p]
hs_splcds HsGroup p
grp
, [TyClGroup p] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TyClGroup p] -> HieM [HieAST Type])
-> [TyClGroup p] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [TyClGroup p]
forall p. HsGroup p -> [TyClGroup p]
hs_tyclds HsGroup p
grp
, [GenLocated SrcSpan (DerivDecl p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (DerivDecl p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (DerivDecl p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (DerivDecl p)]
forall p. HsGroup p -> [LDerivDecl p]
hs_derivds HsGroup p
grp
, [GenLocated SrcSpan (FixitySig p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (FixitySig p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (FixitySig p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (FixitySig p)]
forall p. HsGroup p -> [LFixitySig p]
hs_fixds HsGroup p
grp
, [GenLocated SrcSpan (DefaultDecl p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (DefaultDecl p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (DefaultDecl p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (DefaultDecl p)]
forall p. HsGroup p -> [LDefaultDecl p]
hs_defds HsGroup p
grp
, [GenLocated SrcSpan (ForeignDecl p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (ForeignDecl p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (ForeignDecl p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (ForeignDecl p)]
forall p. HsGroup p -> [LForeignDecl p]
hs_fords HsGroup p
grp
, [GenLocated SrcSpan (WarnDecls p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (WarnDecls p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (WarnDecls p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (WarnDecls p)]
forall p. HsGroup p -> [LWarnDecls p]
hs_warnds HsGroup p
grp
, [GenLocated SrcSpan (AnnDecl p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (AnnDecl p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (AnnDecl p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (AnnDecl p)]
forall p. HsGroup p -> [LAnnDecl p]
hs_annds HsGroup p
grp
, [GenLocated SrcSpan (RuleDecls p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (RuleDecls p)] -> HieM [HieAST Type])
-> [GenLocated SrcSpan (RuleDecls p)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsGroup p -> [GenLocated SrcSpan (RuleDecls p)]
forall p. HsGroup p -> [LRuleDecls p]
hs_ruleds HsGroup p
grp
]
getRealSpan :: SrcSpan -> Maybe Span
getRealSpan :: SrcSpan -> Maybe Span
getRealSpan (RealSrcSpan Span
sp Maybe BufSpan
_) = Span -> Maybe Span
forall a. a -> Maybe a
Just Span
sp
getRealSpan SrcSpan
_ = Maybe Span
forall a. Maybe a
Nothing
grhss_span :: GRHSs p body -> SrcSpan
grhss_span :: forall p body. GRHSs p body -> SrcSpan
grhss_span (GRHSs XCGRHSs p body
_ [LGRHS p body]
xs LHsLocalBinds p
bs) = (SrcSpan -> SrcSpan -> SrcSpan) -> SrcSpan -> [SrcSpan] -> SrcSpan
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (LHsLocalBinds p -> SrcSpan
forall l e. GenLocated l e -> l
getLoc LHsLocalBinds p
bs) ((LGRHS p body -> SrcSpan) -> [LGRHS p body] -> [SrcSpan]
forall a b. (a -> b) -> [a] -> [b]
map LGRHS p body -> SrcSpan
forall l e. GenLocated l e -> l
getLoc [LGRHS p body]
xs)
grhss_span (XGRHSs XXGRHSs p body
_) = FilePath -> SrcSpan
forall a. FilePath -> a
panic FilePath
"XGRHS has no span"
bindingsOnly :: [Context Name] -> HieM [HieAST a]
bindingsOnly :: forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly [] = [HieAST a] -> ReaderT NodeOrigin (StateT HieState Hsc) [HieAST a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
bindingsOnly (C ContextInfo
c Name
n : [Context Name]
xs) = do
NodeOrigin
org <- ReaderT NodeOrigin (StateT HieState Hsc) NodeOrigin
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
[HieAST a]
rest <- [Context Name]
-> ReaderT NodeOrigin (StateT HieState Hsc) [HieAST a]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly [Context Name]
xs
[HieAST a] -> ReaderT NodeOrigin (StateT HieState Hsc) [HieAST a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([HieAST a] -> ReaderT NodeOrigin (StateT HieState Hsc) [HieAST a])
-> [HieAST a]
-> ReaderT NodeOrigin (StateT HieState Hsc) [HieAST a]
forall a b. (a -> b) -> a -> b
$ case Name -> SrcSpan
nameSrcSpan Name
n of
RealSrcSpan Span
span Maybe BufSpan
_ -> SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node (NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
forall a. NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo NodeOrigin
org NodeInfo a
nodeinfo) Span
span [] HieAST a -> [HieAST a] -> [HieAST a]
forall a. a -> [a] -> [a]
: [HieAST a]
rest
where nodeinfo :: NodeInfo a
nodeinfo = Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo Set (FastString, FastString)
forall a. Set a
S.empty [] (Either ModuleName Name -> IdentifierDetails a -> NodeIdentifiers a
forall k a. k -> a -> Map k a
M.singleton (Name -> Either ModuleName Name
forall a b. b -> Either a b
Right Name
n) IdentifierDetails a
info)
info :: IdentifierDetails a
info = IdentifierDetails a
forall a. Monoid a => a
mempty{identInfo :: Set ContextInfo
identInfo = ContextInfo -> Set ContextInfo
forall a. a -> Set a
S.singleton ContextInfo
c}
SrcSpan
_ -> [HieAST a]
rest
concatM :: Monad m => [m [a]] -> m [a]
concatM :: forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM [m [a]]
xs = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[a]] -> [a]) -> m [[a]] -> m [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [m [a]] -> m [[a]]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [m [a]]
xs
data Context a = C ContextInfo a
data RContext a = RC RecFieldContext a
data RFContext a = RFC RecFieldContext (Maybe Span) a
data IEContext a = IEC IEType a
data BindContext a = BC BindType Scope a
data PatSynFieldContext a = PSC (Maybe Span) a
data SigContext a = SC SigInfo a
data SigInfo = SI SigType (Maybe Span)
data SigType = BindSig | ClassSig | InstSig
data EvBindContext a = EvBindContext Scope (Maybe Span) a
data RScoped a = RS Scope a
data PScoped a = PS (Maybe Span)
Scope
Scope
a
deriving (Typeable, Typeable (PScoped a)
Typeable (PScoped a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PScoped a -> c (PScoped a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PScoped a))
-> (PScoped a -> Constr)
-> (PScoped a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PScoped a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PScoped a)))
-> ((forall b. Data b => b -> b) -> PScoped a -> PScoped a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r)
-> (forall u. (forall d. Data d => d -> u) -> PScoped a -> [u])
-> (forall u.
TypeIndex -> (forall d. Data d => d -> u) -> PScoped a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a))
-> Data (PScoped a)
PScoped a -> DataType
PScoped a -> Constr
(forall b. Data b => b -> b) -> PScoped a -> PScoped a
forall {a}. Data a => Typeable (PScoped a)
forall a. Data a => PScoped a -> DataType
forall a. Data a => PScoped a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> PScoped a -> PScoped a
forall a u.
Data a =>
TypeIndex -> (forall d. Data d => d -> u) -> PScoped a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> PScoped a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PScoped a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PScoped a -> c (PScoped a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PScoped a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PScoped a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. TypeIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
TypeIndex -> (forall d. Data d => d -> u) -> PScoped a -> u
forall u. (forall d. Data d => d -> u) -> PScoped a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PScoped a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PScoped a -> c (PScoped a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PScoped a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PScoped a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> PScoped a -> m (PScoped a)
gmapQi :: forall u.
TypeIndex -> (forall d. Data d => d -> u) -> PScoped a -> u
$cgmapQi :: forall a u.
Data a =>
TypeIndex -> (forall d. Data d => d -> u) -> PScoped a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PScoped a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> PScoped a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PScoped a -> r
gmapT :: (forall b. Data b => b -> b) -> PScoped a -> PScoped a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> PScoped a -> PScoped a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PScoped a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PScoped a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PScoped a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PScoped a))
dataTypeOf :: PScoped a -> DataType
$cdataTypeOf :: forall a. Data a => PScoped a -> DataType
toConstr :: PScoped a -> Constr
$ctoConstr :: forall a. Data a => PScoped a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PScoped a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PScoped a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PScoped a -> c (PScoped a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PScoped a -> c (PScoped a)
Data)
data TScoped a = TS TyVarScope a
data TVScoped a = TVS TyVarScope Scope a
listScopes :: Scope -> [Located a] -> [RScoped (Located a)]
listScopes :: forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
_ [] = []
listScopes Scope
rhsScope [Located a
pat] = [Scope -> Located a -> RScoped (Located a)
forall a. Scope -> a -> RScoped a
RS Scope
rhsScope Located a
pat]
listScopes Scope
rhsScope (Located a
pat : [Located a]
pats) = Scope -> Located a -> RScoped (Located a)
forall a. Scope -> a -> RScoped a
RS Scope
sc Located a
pat RScoped (Located a)
-> [RScoped (Located a)] -> [RScoped (Located a)]
forall a. a -> [a] -> [a]
: [RScoped (Located a)]
pats'
where
pats' :: [RScoped (Located a)]
pats'@((RS Scope
scope Located a
p):[RScoped (Located a)]
_) = Scope -> [Located a] -> [RScoped (Located a)]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
rhsScope [Located a]
pats
sc :: Scope
sc = Scope -> Scope -> Scope
combineScopes Scope
scope (Scope -> Scope) -> Scope -> Scope
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ Located a -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located a
p
patScopes
:: Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes :: forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
rsp Scope
useScope Scope
patScope [LPat (GhcPass p)]
xs =
(RScoped (Located (Pat (GhcPass p)))
-> PScoped (Located (Pat (GhcPass p))))
-> [RScoped (Located (Pat (GhcPass p)))]
-> [PScoped (Located (Pat (GhcPass p)))]
forall a b. (a -> b) -> [a] -> [b]
map (\(RS Scope
sc Located (Pat (GhcPass p))
a) -> Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
useScope Scope
sc Located (Pat (GhcPass p))
a) ([RScoped (Located (Pat (GhcPass p)))]
-> [PScoped (Located (Pat (GhcPass p)))])
-> [RScoped (Located (Pat (GhcPass p)))]
-> [PScoped (Located (Pat (GhcPass p)))]
forall a b. (a -> b) -> a -> b
$
Scope
-> [Located (Pat (GhcPass p))]
-> [RScoped (Located (Pat (GhcPass p)))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
patScope [Located (Pat (GhcPass p))]
[LPat (GhcPass p)]
xs
tvScopes
:: TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes :: forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes TyVarScope
tvScope Scope
rhsScope [LHsTyVarBndr flag a]
xs =
(RScoped (LHsTyVarBndr flag a) -> TVScoped (LHsTyVarBndr flag a))
-> [RScoped (LHsTyVarBndr flag a)]
-> [TVScoped (LHsTyVarBndr flag a)]
forall a b. (a -> b) -> [a] -> [b]
map (\(RS Scope
sc LHsTyVarBndr flag a
a)-> TyVarScope
-> Scope -> LHsTyVarBndr flag a -> TVScoped (LHsTyVarBndr flag a)
forall a. TyVarScope -> Scope -> a -> TVScoped a
TVS TyVarScope
tvScope Scope
sc LHsTyVarBndr flag a
a) ([RScoped (LHsTyVarBndr flag a)]
-> [TVScoped (LHsTyVarBndr flag a)])
-> [RScoped (LHsTyVarBndr flag a)]
-> [TVScoped (LHsTyVarBndr flag a)]
forall a b. (a -> b) -> a -> b
$ Scope -> [LHsTyVarBndr flag a] -> [RScoped (LHsTyVarBndr flag a)]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
rhsScope [LHsTyVarBndr flag a]
xs
class HasLoc a where
loc :: a -> SrcSpan
instance HasLoc thing => HasLoc (TScoped thing) where
loc :: TScoped thing -> SrcSpan
loc (TS TyVarScope
_ thing
a) = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
instance HasLoc thing => HasLoc (PScoped thing) where
loc :: PScoped thing -> SrcSpan
loc (PS Maybe Span
_ Scope
_ Scope
_ thing
a) = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
instance HasLoc (LHsQTyVars GhcRn) where
loc :: LHsQTyVars GhcRn -> SrcSpan
loc (HsQTvs XHsQTvs GhcRn
_ [LHsTyVarBndr () GhcRn]
vs) = [LHsTyVarBndr () GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LHsTyVarBndr () GhcRn]
vs
instance HasLoc thing => HasLoc (HsImplicitBndrs a thing) where
loc :: HsImplicitBndrs a thing -> SrcSpan
loc (HsIB XHsIB a thing
_ thing
a) = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
loc HsImplicitBndrs a thing
_ = SrcSpan
noSrcSpan
instance HasLoc thing => HasLoc (HsWildCardBndrs a thing) where
loc :: HsWildCardBndrs a thing -> SrcSpan
loc (HsWC XHsWC a thing
_ thing
a) = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
loc HsWildCardBndrs a thing
_ = SrcSpan
noSrcSpan
instance HasLoc (Located a) where
loc :: Located a -> SrcSpan
loc (L SrcSpan
l a
_) = SrcSpan
l
instance HasLoc a => HasLoc [a] where
loc :: [a] -> SrcSpan
loc [] = SrcSpan
noSrcSpan
loc [a]
xs = (SrcSpan -> SrcSpan -> SrcSpan) -> [SrcSpan] -> SrcSpan
forall a. (a -> a -> a) -> [a] -> a
foldl1' SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans ([SrcSpan] -> SrcSpan) -> [SrcSpan] -> SrcSpan
forall a b. (a -> b) -> a -> b
$ (a -> SrcSpan) -> [a] -> [SrcSpan]
forall a b. (a -> b) -> [a] -> [b]
map a -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [a]
xs
instance HasLoc a => HasLoc (FamEqn s a) where
loc :: FamEqn s a -> SrcSpan
loc (FamEqn XCFamEqn s a
_ Located (IdP s)
a Maybe [LHsTyVarBndr () s]
Nothing HsTyPats s
b LexicalFixity
_ a
c) = (SrcSpan -> SrcSpan -> SrcSpan) -> [SrcSpan] -> SrcSpan
forall a. (a -> a -> a) -> [a] -> a
foldl1' SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans [Located (IdP s) -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc Located (IdP s)
a, HsTyPats s -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc HsTyPats s
b, a -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc a
c]
loc (FamEqn XCFamEqn s a
_ Located (IdP s)
a (Just [LHsTyVarBndr () s]
tvs) HsTyPats s
b LexicalFixity
_ a
c) = (SrcSpan -> SrcSpan -> SrcSpan) -> [SrcSpan] -> SrcSpan
forall a. (a -> a -> a) -> [a] -> a
foldl1' SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans
[Located (IdP s) -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc Located (IdP s)
a, [LHsTyVarBndr () s] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LHsTyVarBndr () s]
tvs, HsTyPats s -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc HsTyPats s
b, a -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc a
c]
loc FamEqn s a
_ = SrcSpan
noSrcSpan
instance (HasLoc tm, HasLoc ty) => HasLoc (HsArg tm ty) where
loc :: HsArg tm ty -> SrcSpan
loc (HsValArg tm
tm) = tm -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc tm
tm
loc (HsTypeArg SrcSpan
_ ty
ty) = ty -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc ty
ty
loc (HsArgPar SrcSpan
sp) = SrcSpan
sp
instance HasLoc (HsDataDefn GhcRn) where
loc :: HsDataDefn GhcRn -> SrcSpan
loc def :: HsDataDefn GhcRn
def@(HsDataDefn{}) = [LConDecl GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc ([LConDecl GhcRn] -> SrcSpan) -> [LConDecl GhcRn] -> SrcSpan
forall a b. (a -> b) -> a -> b
$ HsDataDefn GhcRn -> [LConDecl GhcRn]
forall pass. HsDataDefn pass -> [LConDecl pass]
dd_cons HsDataDefn GhcRn
def
class HasRealDataConName p where
getRealDataCon :: XRecordCon p -> Located (IdP p) -> Located (IdP p)
instance HasRealDataConName GhcRn where
getRealDataCon :: XRecordCon GhcRn -> Located (IdP GhcRn) -> Located (IdP GhcRn)
getRealDataCon XRecordCon GhcRn
_ Located (IdP GhcRn)
n = Located (IdP GhcRn)
n
instance HasRealDataConName GhcTc where
getRealDataCon :: XRecordCon GhcTc -> Located (IdP GhcTc) -> Located (IdP GhcTc)
getRealDataCon RecordConTc{rcon_con_like :: RecordConTc -> ConLike
rcon_con_like = ConLike
con} (L SrcSpan
sp IdP GhcTc
var) =
SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
sp (Id -> Name -> Id
setVarName Id
IdP GhcTc
var (ConLike -> Name
conLikeName ConLike
con))
class ToHie a where
toHie :: a -> HieM [HieAST Type]
class HasType a where
getTypeNode :: a -> HieM [HieAST Type]
instance (ToHie a) => ToHie [a] where
toHie :: [a] -> HieM [HieAST Type]
toHie = (a -> HieM [HieAST Type]) -> [a] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie
instance (ToHie a) => ToHie (Bag a) where
toHie :: Bag a -> HieM [HieAST Type]
toHie = [a] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([a] -> HieM [HieAST Type])
-> (Bag a -> [a]) -> Bag a -> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bag a -> [a]
forall a. Bag a -> [a]
bagToList
instance (ToHie a) => ToHie (Maybe a) where
toHie :: Maybe a -> HieM [HieAST Type]
toHie = HieM [HieAST Type]
-> (a -> HieM [HieAST Type]) -> Maybe a -> HieM [HieAST Type]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie
instance ToHie (IEContext (Located ModuleName)) where
toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type]
toHie (IEC IEType
c (L (RealSrcSpan Span
span Maybe BufSpan
_) ModuleName
mname)) = do
NodeOrigin
org <- ReaderT NodeOrigin (StateT HieState Hsc) NodeOrigin
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
[HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([HieAST Type] -> HieM [HieAST Type])
-> [HieAST Type] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ [SourcedNodeInfo Type -> Span -> [HieAST Type] -> HieAST Type
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node (NodeOrigin -> NodeInfo Type -> SourcedNodeInfo Type
forall a. NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo NodeOrigin
org (NodeInfo Type -> SourcedNodeInfo Type)
-> NodeInfo Type -> SourcedNodeInfo Type
forall a b. (a -> b) -> a -> b
$ Set (FastString, FastString)
-> [Type] -> NodeIdentifiers Type -> NodeInfo Type
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo Set (FastString, FastString)
forall a. Set a
S.empty [] NodeIdentifiers Type
idents) Span
span []]
where details :: IdentifierDetails Type
details = IdentifierDetails Type
forall a. Monoid a => a
mempty{identInfo :: Set ContextInfo
identInfo = ContextInfo -> Set ContextInfo
forall a. a -> Set a
S.singleton (IEType -> ContextInfo
IEThing IEType
c)}
idents :: NodeIdentifiers Type
idents = Either ModuleName Name
-> IdentifierDetails Type -> NodeIdentifiers Type
forall k a. k -> a -> Map k a
M.singleton (ModuleName -> Either ModuleName Name
forall a b. a -> Either a b
Left ModuleName
mname) IdentifierDetails Type
details
toHie IEContext (Located ModuleName)
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (Context (Located Var)) where
toHie :: Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
toHie Context (GenLocated SrcSpan Id)
c = case Context (GenLocated SrcSpan Id)
c of
C ContextInfo
context (L (RealSrcSpan Span
span Maybe BufSpan
_) Id
name')
| Id -> Unique
varUnique Id
name' Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== TypeIndex -> Unique
mkBuiltinUnique TypeIndex
1 -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
| Bool
otherwise -> do
NameEnv Id
m <- StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id))
-> StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id)
forall a b. (a -> b) -> a -> b
$ (HieState -> NameEnv Id) -> StateT HieState Hsc (NameEnv Id)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets HieState -> NameEnv Id
name_remapping
NodeOrigin
org <- ReaderT NodeOrigin (StateT HieState Hsc) NodeOrigin
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
let name :: Id
name = case NameEnv Id -> Name -> Maybe Id
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv NameEnv Id
m (Id -> Name
varName Id
name') of
Just Id
var -> Id
var
Maybe Id
Nothing-> Id
name'
ty :: Type
ty = case Id -> Maybe DataCon
isDataConId_maybe Id
name' of
Maybe DataCon
Nothing -> Id -> Type
varType Id
name'
Just DataCon
dc -> DataCon -> Type
dataConNonlinearType DataCon
dc
[HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
[SourcedNodeInfo Type -> Span -> [HieAST Type] -> HieAST Type
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node
(NodeOrigin -> NodeInfo Type -> SourcedNodeInfo Type
forall a. NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo NodeOrigin
org (NodeInfo Type -> SourcedNodeInfo Type)
-> NodeInfo Type -> SourcedNodeInfo Type
forall a b. (a -> b) -> a -> b
$ Set (FastString, FastString)
-> [Type] -> NodeIdentifiers Type -> NodeInfo Type
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo Set (FastString, FastString)
forall a. Set a
S.empty [] (NodeIdentifiers Type -> NodeInfo Type)
-> NodeIdentifiers Type -> NodeInfo Type
forall a b. (a -> b) -> a -> b
$
Either ModuleName Name
-> IdentifierDetails Type -> NodeIdentifiers Type
forall k a. k -> a -> Map k a
M.singleton (Name -> Either ModuleName Name
forall a b. b -> Either a b
Right (Name -> Either ModuleName Name) -> Name -> Either ModuleName Name
forall a b. (a -> b) -> a -> b
$ Id -> Name
varName Id
name)
(Maybe Type -> Set ContextInfo -> IdentifierDetails Type
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails (Type -> Maybe Type
forall a. a -> Maybe a
Just Type
ty)
(ContextInfo -> Set ContextInfo
forall a. a -> Set a
S.singleton ContextInfo
context)))
Span
span
[]]
C (EvidenceVarBind EvVarSource
i Scope
_ Maybe Span
sp) (L SrcSpan
_ Id
name) -> do
Id -> ContextInfo -> HieM ()
addUnlocatedEvBind Id
name (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind EvVarSource
i Scope
ModuleScope Maybe Span
sp)
[HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
Context (GenLocated SrcSpan Id)
_ -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (Context (Located Name)) where
toHie :: Context (Located Name) -> HieM [HieAST Type]
toHie Context (Located Name)
c = case Context (Located Name)
c of
C ContextInfo
context (L (RealSrcSpan Span
span Maybe BufSpan
_) Name
name')
| Name -> Unique
nameUnique Name
name' Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== TypeIndex -> Unique
mkBuiltinUnique TypeIndex
1 -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
| Bool
otherwise -> do
NameEnv Id
m <- StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id))
-> StateT HieState Hsc (NameEnv Id)
-> ReaderT NodeOrigin (StateT HieState Hsc) (NameEnv Id)
forall a b. (a -> b) -> a -> b
$ (HieState -> NameEnv Id) -> StateT HieState Hsc (NameEnv Id)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets HieState -> NameEnv Id
name_remapping
NodeOrigin
org <- ReaderT NodeOrigin (StateT HieState Hsc) NodeOrigin
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
let name :: Name
name = case NameEnv Id -> Name -> Maybe Id
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv NameEnv Id
m Name
name' of
Just Id
var -> Id -> Name
varName Id
var
Maybe Id
Nothing -> Name
name'
[HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
[SourcedNodeInfo Type -> Span -> [HieAST Type] -> HieAST Type
forall a. SourcedNodeInfo a -> Span -> [HieAST a] -> HieAST a
Node
(NodeOrigin -> NodeInfo Type -> SourcedNodeInfo Type
forall a. NodeOrigin -> NodeInfo a -> SourcedNodeInfo a
mkSourcedNodeInfo NodeOrigin
org (NodeInfo Type -> SourcedNodeInfo Type)
-> NodeInfo Type -> SourcedNodeInfo Type
forall a b. (a -> b) -> a -> b
$ Set (FastString, FastString)
-> [Type] -> NodeIdentifiers Type -> NodeInfo Type
forall a.
Set (FastString, FastString)
-> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo Set (FastString, FastString)
forall a. Set a
S.empty [] (NodeIdentifiers Type -> NodeInfo Type)
-> NodeIdentifiers Type -> NodeInfo Type
forall a b. (a -> b) -> a -> b
$
Either ModuleName Name
-> IdentifierDetails Type -> NodeIdentifiers Type
forall k a. k -> a -> Map k a
M.singleton (Name -> Either ModuleName Name
forall a b. b -> Either a b
Right Name
name)
(Maybe Type -> Set ContextInfo -> IdentifierDetails Type
forall a. Maybe a -> Set ContextInfo -> IdentifierDetails a
IdentifierDetails Maybe Type
forall a. Maybe a
Nothing
(ContextInfo -> Set ContextInfo
forall a. a -> Set a
S.singleton ContextInfo
context)))
Span
span
[]]
Context (Located Name)
_ -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
evVarsOfTermList :: EvTerm -> [EvId]
evVarsOfTermList :: EvTerm -> [Id]
evVarsOfTermList (EvExpr EvExpr
e) = InterestingVarFun -> EvExpr -> [Id]
exprSomeFreeVarsList InterestingVarFun
isEvVar EvExpr
e
evVarsOfTermList (EvTypeable Type
_ EvTypeable
ev) =
case EvTypeable
ev of
EvTypeableTyCon TyCon
_ [EvTerm]
e -> (EvTerm -> [Id]) -> [EvTerm] -> [Id]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap EvTerm -> [Id]
evVarsOfTermList [EvTerm]
e
EvTypeableTyApp EvTerm
e1 EvTerm
e2 -> (EvTerm -> [Id]) -> [EvTerm] -> [Id]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap EvTerm -> [Id]
evVarsOfTermList [EvTerm
e1,EvTerm
e2]
EvTypeableTrFun EvTerm
e1 EvTerm
e2 EvTerm
e3 -> (EvTerm -> [Id]) -> [EvTerm] -> [Id]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap EvTerm -> [Id]
evVarsOfTermList [EvTerm
e1,EvTerm
e2,EvTerm
e3]
EvTypeableTyLit EvTerm
e -> EvTerm -> [Id]
evVarsOfTermList EvTerm
e
evVarsOfTermList (EvFun{}) = []
instance ToHie (EvBindContext (Located TcEvBinds)) where
toHie :: EvBindContext (GenLocated SrcSpan TcEvBinds) -> HieM [HieAST Type]
toHie (EvBindContext Scope
sc Maybe Span
sp (L SrcSpan
span (EvBinds Bag EvBind
bs)))
= (EvBind -> HieM [HieAST Type]) -> [EvBind] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM EvBind -> HieM [HieAST Type]
go ([EvBind] -> HieM [HieAST Type]) -> [EvBind] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Bag EvBind -> [EvBind]
forall a. Bag a -> [a]
bagToList Bag EvBind
bs
where
go :: EvBind -> HieM [HieAST Type]
go EvBind
evbind = do
let evDeps :: [Id]
evDeps = EvTerm -> [Id]
evVarsOfTermList (EvTerm -> [Id]) -> EvTerm -> [Id]
forall a b. (a -> b) -> a -> b
$ EvBind -> EvTerm
eb_rhs EvBind
evbind
depNames :: EvBindDeps
depNames = [Name] -> EvBindDeps
EvBindDeps ([Name] -> EvBindDeps) -> [Name] -> EvBindDeps
forall a b. (a -> b) -> a -> b
$ (Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
varName [Id]
evDeps
[HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind (EvBindDeps -> EvVarSource
EvLetBind EvBindDeps
depNames) (Scope -> Scope -> Scope
combineScopes Scope
sc (SrcSpan -> Scope
mkScope SrcSpan
span)) Maybe Span
sp)
(SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
span (Id -> GenLocated SrcSpan Id) -> Id -> GenLocated SrcSpan Id
forall a b. (a -> b) -> a -> b
$ EvBind -> Id
eb_lhs EvBind
evbind))
, [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type])
-> [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Id -> Context (GenLocated SrcSpan Id))
-> [Id] -> [Context (GenLocated SrcSpan Id)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C ContextInfo
EvidenceVarUse (GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id))
-> (Id -> GenLocated SrcSpan Id)
-> Id
-> Context (GenLocated SrcSpan Id)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
span) ([Id] -> [Context (GenLocated SrcSpan Id)])
-> [Id] -> [Context (GenLocated SrcSpan Id)]
forall a b. (a -> b) -> a -> b
$ [Id]
evDeps
]
toHie EvBindContext (GenLocated SrcSpan TcEvBinds)
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (Located HsWrapper) where
toHie :: Located HsWrapper -> HieM [HieAST Type]
toHie (L SrcSpan
osp HsWrapper
wrap)
= case HsWrapper
wrap of
(WpLet TcEvBinds
bs) -> EvBindContext (GenLocated SrcSpan TcEvBinds) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type])
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> Maybe Span
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a. Scope -> Maybe Span -> a -> EvBindContext a
EvBindContext (SrcSpan -> Scope
mkScope SrcSpan
osp) (SrcSpan -> Maybe Span
getRealSpan SrcSpan
osp) (SrcSpan -> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp TcEvBinds
bs)
(WpCompose HsWrapper
a HsWrapper
b) -> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp HsWrapper
a), Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp HsWrapper
b)]
(WpFun HsWrapper
a HsWrapper
b Scaled Type
_ SDoc
_) -> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp HsWrapper
a), Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp HsWrapper
b)]
(WpEvLam Id
a) ->
Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind EvVarSource
EvWrapperBind (SrcSpan -> Scope
mkScope SrcSpan
osp) (SrcSpan -> Maybe Span
getRealSpan SrcSpan
osp))
(GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id))
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp Id
a
(WpEvApp EvTerm
a) ->
(Id -> HieM [HieAST Type]) -> [Id] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type])
-> (Id -> Context (GenLocated SrcSpan Id))
-> Id
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C ContextInfo
EvidenceVarUse (GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id))
-> (Id -> GenLocated SrcSpan Id)
-> Id
-> Context (GenLocated SrcSpan Id)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
osp) ([Id] -> HieM [HieAST Type]) -> [Id] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ EvTerm -> [Id]
evVarsOfTermList EvTerm
a
HsWrapper
_ -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance HiePass p => HasType (LHsBind (GhcPass p)) where
getTypeNode :: LHsBind (GhcPass p) -> HieM [HieAST Type]
getTypeNode (L SrcSpan
spn HsBindLR (GhcPass p) (GhcPass p)
bind) =
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieRn -> HsBindLR (GhcPass p) (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsBindLR (GhcPass p) (GhcPass p)
bind SrcSpan
spn
HiePassEv p
HieTc -> case HsBindLR (GhcPass p) (GhcPass p)
bind of
FunBind{fun_id :: forall idL idR. HsBindLR idL idR -> Located (IdP idL)
fun_id = Located (IdP (GhcPass p))
name} -> HsBindLR (GhcPass p) (GhcPass p)
-> SrcSpan -> Type -> HieM [HieAST Type]
forall (m :: * -> *) a.
(Monad m, Data a) =>
a -> SrcSpan -> Type -> ReaderT NodeOrigin m [HieAST Type]
makeTypeNode HsBindLR (GhcPass p) (GhcPass p)
bind SrcSpan
spn (Id -> Type
varType (Id -> Type) -> Id -> Type
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan Id -> Id
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpan Id
Located (IdP (GhcPass p))
name)
HsBindLR (GhcPass p) (GhcPass p)
_ -> HsBindLR (GhcPass p) (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsBindLR (GhcPass p) (GhcPass p)
bind SrcSpan
spn
instance HiePass p => HasType (Located (Pat (GhcPass p))) where
getTypeNode :: Located (Pat (GhcPass p)) -> HieM [HieAST Type]
getTypeNode (L SrcSpan
spn Pat (GhcPass p)
pat) =
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieRn -> Pat (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode Pat (GhcPass p)
pat SrcSpan
spn
HiePassEv p
HieTc -> Pat (GhcPass p) -> SrcSpan -> Type -> HieM [HieAST Type]
forall (m :: * -> *) a.
(Monad m, Data a) =>
a -> SrcSpan -> Type -> ReaderT NodeOrigin m [HieAST Type]
makeTypeNode Pat (GhcPass p)
pat SrcSpan
spn (Pat GhcTc -> Type
hsPatType Pat (GhcPass p)
Pat GhcTc
pat)
instance HiePass p => HasType (LHsExpr (GhcPass p)) where
getTypeNode :: LHsExpr (GhcPass p) -> HieM [HieAST Type]
getTypeNode e :: LHsExpr (GhcPass p)
e@(L SrcSpan
spn HsExpr (GhcPass p)
e') =
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieRn -> HsExpr (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsExpr (GhcPass p)
e' SrcSpan
spn
HiePassEv p
HieTc ->
let tyOpt :: Maybe Type
tyOpt = case HsExpr (GhcPass p)
e' of
HsLit XLitE (GhcPass p)
_ HsLit (GhcPass p)
l -> Type -> Maybe Type
forall a. a -> Maybe a
Just (HsLit (GhcPass p) -> Type
forall (p :: Pass). HsLit (GhcPass p) -> Type
hsLitType HsLit (GhcPass p)
l)
HsOverLit XOverLitE (GhcPass p)
_ HsOverLit (GhcPass p)
o -> Type -> Maybe Type
forall a. a -> Maybe a
Just (HsOverLit GhcTc -> Type
overLitType HsOverLit (GhcPass p)
HsOverLit GhcTc
o)
HsConLikeOut XConLikeOut (GhcPass p)
_ (RealDataCon DataCon
con) -> Type -> Maybe Type
forall a. a -> Maybe a
Just (DataCon -> Type
dataConNonlinearType DataCon
con)
HsLam XLam (GhcPass p)
_ (MG { mg_ext :: forall p body. MatchGroup p body -> XMG p body
mg_ext = XMG (GhcPass p) (LHsExpr (GhcPass p))
groupTy }) -> Type -> Maybe Type
forall a. a -> Maybe a
Just (MatchGroupTc -> Type
matchGroupType XMG (GhcPass p) (LHsExpr (GhcPass p))
MatchGroupTc
groupTy)
HsLamCase XLamCase (GhcPass p)
_ (MG { mg_ext :: forall p body. MatchGroup p body -> XMG p body
mg_ext = XMG (GhcPass p) (LHsExpr (GhcPass p))
groupTy }) -> Type -> Maybe Type
forall a. a -> Maybe a
Just (MatchGroupTc -> Type
matchGroupType XMG (GhcPass p) (LHsExpr (GhcPass p))
MatchGroupTc
groupTy)
HsCase XCase (GhcPass p)
_ LHsExpr (GhcPass p)
_ (MG { mg_ext :: forall p body. MatchGroup p body -> XMG p body
mg_ext = XMG (GhcPass p) (LHsExpr (GhcPass p))
groupTy }) -> Type -> Maybe Type
forall a. a -> Maybe a
Just (MatchGroupTc -> Type
mg_res_ty XMG (GhcPass p) (LHsExpr (GhcPass p))
MatchGroupTc
groupTy)
ExplicitList XExplicitList (GhcPass p)
ty Maybe (SyntaxExpr (GhcPass p))
_ [LHsExpr (GhcPass p)]
_ -> Type -> Maybe Type
forall a. a -> Maybe a
Just (Type -> Type
mkListTy Type
XExplicitList (GhcPass p)
ty)
ExplicitSum XExplicitSum (GhcPass p)
ty TypeIndex
_ TypeIndex
_ LHsExpr (GhcPass p)
_ -> Type -> Maybe Type
forall a. a -> Maybe a
Just ([Type] -> Type
mkSumTy [Type]
XExplicitSum (GhcPass p)
ty)
HsDo XDo (GhcPass p)
ty HsStmtContext GhcRn
_ Located [ExprLStmt (GhcPass p)]
_ -> Type -> Maybe Type
forall a. a -> Maybe a
Just Type
XDo (GhcPass p)
ty
HsMultiIf XMultiIf (GhcPass p)
ty [LGRHS (GhcPass p) (LHsExpr (GhcPass p))]
_ -> Type -> Maybe Type
forall a. a -> Maybe a
Just Type
XMultiIf (GhcPass p)
ty
HsExpr (GhcPass p)
_ -> Maybe Type
forall a. Maybe a
Nothing
in
case Maybe Type
tyOpt of
Just Type
t -> HsExpr (GhcPass p) -> SrcSpan -> Type -> HieM [HieAST Type]
forall (m :: * -> *) a.
(Monad m, Data a) =>
a -> SrcSpan -> Type -> ReaderT NodeOrigin m [HieAST Type]
makeTypeNode HsExpr (GhcPass p)
e' SrcSpan
spn Type
t
Maybe Type
Nothing
| HsExpr GhcTc -> Bool
skipDesugaring HsExpr (GhcPass p)
HsExpr GhcTc
e' -> HieM [HieAST Type]
fallback
| Bool
otherwise -> do
HscEnv
hs_env <- StateT HieState Hsc HscEnv
-> ReaderT NodeOrigin (StateT HieState Hsc) HscEnv
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT HieState Hsc HscEnv
-> ReaderT NodeOrigin (StateT HieState Hsc) HscEnv)
-> StateT HieState Hsc HscEnv
-> ReaderT NodeOrigin (StateT HieState Hsc) HscEnv
forall a b. (a -> b) -> a -> b
$ Hsc HscEnv -> StateT HieState Hsc HscEnv
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Hsc HscEnv -> StateT HieState Hsc HscEnv)
-> Hsc HscEnv -> StateT HieState Hsc HscEnv
forall a b. (a -> b) -> a -> b
$ (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv)
-> (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a b. (a -> b) -> a -> b
$ \HscEnv
e WarningMessages
w -> (HscEnv, WarningMessages) -> IO (HscEnv, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv
e,WarningMessages
w)
(Messages
_,Maybe EvExpr
mbe) <- IO (Messages, Maybe EvExpr)
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Messages, Maybe EvExpr)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Messages, Maybe EvExpr)
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Messages, Maybe EvExpr))
-> IO (Messages, Maybe EvExpr)
-> ReaderT
NodeOrigin (StateT HieState Hsc) (Messages, Maybe EvExpr)
forall a b. (a -> b) -> a -> b
$ HscEnv -> LHsExpr GhcTc -> IO (Messages, Maybe EvExpr)
deSugarExpr HscEnv
hs_env LHsExpr (GhcPass p)
LHsExpr GhcTc
e
HieM [HieAST Type]
-> (EvExpr -> HieM [HieAST Type])
-> Maybe EvExpr
-> HieM [HieAST Type]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HieM [HieAST Type]
fallback (HsExpr (GhcPass p) -> SrcSpan -> Type -> HieM [HieAST Type]
forall (m :: * -> *) a.
(Monad m, Data a) =>
a -> SrcSpan -> Type -> ReaderT NodeOrigin m [HieAST Type]
makeTypeNode HsExpr (GhcPass p)
e' SrcSpan
spn (Type -> HieM [HieAST Type])
-> (EvExpr -> Type) -> EvExpr -> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EvExpr -> Type
exprType) Maybe EvExpr
mbe
where
fallback :: HieM [HieAST Type]
fallback = HsExpr (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsExpr (GhcPass p)
e' SrcSpan
spn
matchGroupType :: MatchGroupTc -> Type
matchGroupType :: MatchGroupTc -> Type
matchGroupType (MatchGroupTc [Scaled Type]
args Type
res) = [Scaled Type] -> Type -> Type
mkVisFunTys [Scaled Type]
args Type
res
skipDesugaring :: HsExpr GhcTc -> Bool
skipDesugaring :: HsExpr GhcTc -> Bool
skipDesugaring HsExpr GhcTc
e = case HsExpr GhcTc
e of
HsVar{} -> Bool
False
HsUnboundVar{} -> Bool
False
HsConLikeOut{} -> Bool
False
HsRecFld{} -> Bool
False
HsOverLabel{} -> Bool
False
HsIPVar{} -> Bool
False
XExpr (WrapExpr {}) -> Bool
False
HsExpr GhcTc
_ -> Bool
True
data HiePassEv p where
HieRn :: HiePassEv 'Renamed
HieTc :: HiePassEv 'Typechecked
class ( IsPass p
, HiePass (NoGhcTcPass p)
, ModifyState (IdGhcP p)
, Data (GRHS (GhcPass p) (Located (HsExpr (GhcPass p))))
, Data (HsExpr (GhcPass p))
, Data (HsCmd (GhcPass p))
, Data (AmbiguousFieldOcc (GhcPass p))
, Data (HsCmdTop (GhcPass p))
, Data (GRHS (GhcPass p) (Located (HsCmd (GhcPass p))))
, Data (HsSplice (GhcPass p))
, Data (HsLocalBinds (GhcPass p))
, Data (FieldOcc (GhcPass p))
, Data (HsTupArg (GhcPass p))
, Data (IPBind (GhcPass p))
, ToHie (Context (Located (IdGhcP p)))
, ToHie (RFContext (Located (AmbiguousFieldOcc (GhcPass p))))
, ToHie (RFContext (Located (FieldOcc (GhcPass p))))
, ToHie (TScoped (LHsWcType (GhcPass (NoGhcTcPass p))))
, ToHie (TScoped (LHsSigWcType (GhcPass (NoGhcTcPass p))))
, HasRealDataConName (GhcPass p)
)
=> HiePass p where
hiePass :: HiePassEv p
instance HiePass 'Renamed where
hiePass :: HiePassEv 'Renamed
hiePass = HiePassEv 'Renamed
HieRn
instance HiePass 'Typechecked where
hiePass :: HiePassEv 'Typechecked
hiePass = HiePassEv 'Typechecked
HieTc
instance HiePass p => ToHie (BindContext (LHsBind (GhcPass p))) where
toHie :: BindContext (LHsBind (GhcPass p)) -> HieM [HieAST Type]
toHie (BC BindType
context Scope
scope b :: LHsBind (GhcPass p)
b@(L SrcSpan
span HsBindLR (GhcPass p) (GhcPass p)
bind)) =
[HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ LHsBind (GhcPass p) -> HieM [HieAST Type]
forall a. HasType a => a -> HieM [HieAST Type]
getTypeNode LHsBind (GhcPass p)
b HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsBindLR (GhcPass p) (GhcPass p)
bind of
FunBind{fun_id :: forall idL idR. HsBindLR idL idR -> Located (IdP idL)
fun_id = Located (IdP (GhcPass p))
name, fun_matches :: forall idL idR. HsBindLR idL idR -> MatchGroup idR (LHsExpr idR)
fun_matches = MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
matches, fun_ext :: forall idL idR. HsBindLR idL idR -> XFunBind idL idR
fun_ext = XFunBind (GhcPass p) (GhcPass p)
wrap} ->
[ Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (BindType -> Scope -> Maybe Span -> ContextInfo
ValBind BindType
context Scope
scope (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located (IdGhcP p)
Located (IdP (GhcPass p))
name
, MatchGroup (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
matches
, case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc -> Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Located HsWrapper -> HieM [HieAST Type])
-> Located HsWrapper -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
span XFunBind (GhcPass p) (GhcPass p)
HsWrapper
wrap
HiePassEv p
_ -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
]
PatBind{pat_lhs :: forall idL idR. HsBindLR idL idR -> LPat idL
pat_lhs = LPat (GhcPass p)
lhs, pat_rhs :: forall idL idR. HsBindLR idL idR -> GRHSs idR (LHsExpr idR)
pat_rhs = GRHSs (GhcPass p) (LHsExpr (GhcPass p))
rhs} ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS (SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Scope
scope Scope
NoScope Located (Pat (GhcPass p))
LPat (GhcPass p)
lhs
, GRHSs (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GRHSs (GhcPass p) (LHsExpr (GhcPass p))
rhs
]
VarBind{var_rhs :: forall idL idR. HsBindLR idL idR -> LHsExpr idR
var_rhs = LHsExpr (GhcPass p)
expr} ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
AbsBinds{ abs_exports :: forall idL idR. HsBindLR idL idR -> [ABExport idL]
abs_exports = [ABExport (GhcPass p)]
xs, abs_binds :: forall idL idR. HsBindLR idL idR -> LHsBinds idL
abs_binds = LHsBinds (GhcPass p)
binds
, abs_ev_binds :: forall idL idR. HsBindLR idL idR -> [TcEvBinds]
abs_ev_binds = [TcEvBinds]
ev_binds
, abs_ev_vars :: forall idL idR. HsBindLR idL idR -> [Id]
abs_ev_vars = [Id]
ev_vars } ->
[ StateT HieState Hsc () -> HieM ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((HieState -> HieState) -> StateT HieState Hsc ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify ([ABExport (GhcPass p)] -> HieState -> HieState
forall p.
ModifyState (IdP p) =>
[ABExport p] -> HieState -> HieState
modifyState [ABExport (GhcPass p)]
xs)) HieM () -> HieM [HieAST Type] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Bag (BindContext (LHsBind (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Bag (BindContext (LHsBind (GhcPass p))) -> HieM [HieAST Type])
-> Bag (BindContext (LHsBind (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsBind (GhcPass p) -> BindContext (LHsBind (GhcPass p)))
-> LHsBinds (GhcPass p) -> Bag (BindContext (LHsBind (GhcPass p)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BindType
-> Scope
-> LHsBind (GhcPass p)
-> BindContext (LHsBind (GhcPass p))
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
context Scope
scope) LHsBinds (GhcPass p)
binds)
, [Located HsWrapper] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Located HsWrapper] -> HieM [HieAST Type])
-> [Located HsWrapper] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (ABExport (GhcPass p) -> Located HsWrapper)
-> [ABExport (GhcPass p)] -> [Located HsWrapper]
forall a b. (a -> b) -> [a] -> [b]
map (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
span (HsWrapper -> Located HsWrapper)
-> (ABExport (GhcPass p) -> HsWrapper)
-> ABExport (GhcPass p)
-> Located HsWrapper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ABExport (GhcPass p) -> HsWrapper
forall p. ABExport p -> HsWrapper
abe_wrap) [ABExport (GhcPass p)]
xs
, [EvBindContext (GenLocated SrcSpan TcEvBinds)]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([EvBindContext (GenLocated SrcSpan TcEvBinds)]
-> HieM [HieAST Type])
-> [EvBindContext (GenLocated SrcSpan TcEvBinds)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
(TcEvBinds -> EvBindContext (GenLocated SrcSpan TcEvBinds))
-> [TcEvBinds] -> [EvBindContext (GenLocated SrcSpan TcEvBinds)]
forall a b. (a -> b) -> [a] -> [b]
map (Scope
-> Maybe Span
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a. Scope -> Maybe Span -> a -> EvBindContext a
EvBindContext (SrcSpan -> Scope
mkScope SrcSpan
span) (SrcSpan -> Maybe Span
getRealSpan SrcSpan
span)
(GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds))
-> (TcEvBinds -> GenLocated SrcSpan TcEvBinds)
-> TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall l e. l -> e -> GenLocated l e
L SrcSpan
span) [TcEvBinds]
ev_binds
, [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type])
-> [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
(Id -> Context (GenLocated SrcSpan Id))
-> [Id] -> [Context (GenLocated SrcSpan Id)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind EvVarSource
EvSigBind
(SrcSpan -> Scope
mkScope SrcSpan
span)
(SrcSpan -> Maybe Span
getRealSpan SrcSpan
span))
(GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id))
-> (Id -> GenLocated SrcSpan Id)
-> Id
-> Context (GenLocated SrcSpan Id)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
span) [Id]
ev_vars
]
PatSynBind XPatSynBind (GhcPass p) (GhcPass p)
_ PatSynBind (GhcPass p) (GhcPass p)
psb ->
[ GenLocated SrcSpan (PatSynBind (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (PatSynBind (GhcPass p) (GhcPass p))
-> HieM [HieAST Type])
-> GenLocated SrcSpan (PatSynBind (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> PatSynBind (GhcPass p) (GhcPass p)
-> GenLocated SrcSpan (PatSynBind (GhcPass p) (GhcPass p))
forall l e. l -> e -> GenLocated l e
L SrcSpan
span PatSynBind (GhcPass p) (GhcPass p)
psb
]
instance ( HiePass p
, ToHie (Located body)
, Data body
) => ToHie (MatchGroup (GhcPass p) (Located body)) where
toHie :: MatchGroup (GhcPass p) (Located body) -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (Located body)
mg = case MatchGroup (GhcPass p) (Located body)
mg of
MG{ mg_alts :: forall p body. MatchGroup p body -> Located [LMatch p body]
mg_alts = (L SrcSpan
span [LMatch (GhcPass p) (Located body)]
alts) , mg_origin :: forall p body. MatchGroup p body -> Origin
mg_origin = Origin
origin} ->
(NodeOrigin -> NodeOrigin)
-> HieM [HieAST Type] -> HieM [HieAST Type]
forall r (m :: * -> *) a.
(r -> r) -> ReaderT r m a -> ReaderT r m a
local (Origin -> NodeOrigin -> NodeOrigin
setOrigin Origin
origin) (HieM [HieAST Type] -> HieM [HieAST Type])
-> HieM [HieAST Type] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
span
, [LMatch (GhcPass p) (Located body)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LMatch (GhcPass p) (Located body)]
alts
]
setOrigin :: Origin -> NodeOrigin -> NodeOrigin
setOrigin :: Origin -> NodeOrigin -> NodeOrigin
setOrigin Origin
FromSource NodeOrigin
_ = NodeOrigin
SourceInfo
setOrigin Origin
Generated NodeOrigin
_ = NodeOrigin
GeneratedInfo
instance HiePass p => ToHie (Located (PatSynBind (GhcPass p) (GhcPass p))) where
toHie :: Located (PatSynBind (GhcPass p) (GhcPass p)) -> HieM [HieAST Type]
toHie (L SrcSpan
sp PatSynBind (GhcPass p) (GhcPass p)
psb) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case PatSynBind (GhcPass p) (GhcPass p)
psb of
PSB{psb_id :: forall idL idR. PatSynBind idL idR -> Located (IdP idL)
psb_id=Located (IdP (GhcPass p))
var, psb_args :: forall idL idR.
PatSynBind idL idR -> HsPatSynDetails (Located (IdP idR))
psb_args=HsPatSynDetails (Located (IdP (GhcPass p)))
dets, psb_def :: forall idL idR. PatSynBind idL idR -> LPat idR
psb_def=LPat (GhcPass p)
pat, psb_dir :: forall idL idR. PatSynBind idL idR -> HsPatSynDir idR
psb_dir=HsPatSynDir (GhcPass p)
dir} ->
[ Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
PatSynDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
sp) Located (IdGhcP p)
Located (IdP (GhcPass p))
var
, HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HieM [HieAST Type])
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsConDetails
(Located (IdGhcP p)) [RecordPatSynField (Located (IdGhcP p))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
toBind HsConDetails
(Located (IdGhcP p)) [RecordPatSynField (Located (IdGhcP p))]
HsPatSynDetails (Located (IdP (GhcPass p)))
dets
, PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
forall a. Maybe a
Nothing Scope
lhsScope Scope
patScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
, HsPatSynDir (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsPatSynDir (GhcPass p)
dir
]
where
lhsScope :: Scope
lhsScope = Scope -> Scope -> Scope
combineScopes Scope
varScope Scope
detScope
varScope :: Scope
varScope = Located (IdGhcP p) -> Scope
forall a. Located a -> Scope
mkLScope Located (IdGhcP p)
Located (IdP (GhcPass p))
var
patScope :: Scope
patScope = SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ Located (Pat (GhcPass p)) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
detScope :: Scope
detScope = case HsPatSynDetails (Located (IdP (GhcPass p)))
dets of
(PrefixCon [Located (IdP (GhcPass p))]
args) -> (Scope -> Scope -> Scope) -> Scope -> [Scope] -> Scope
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Scope -> Scope -> Scope
combineScopes Scope
NoScope ([Scope] -> Scope) -> [Scope] -> Scope
forall a b. (a -> b) -> a -> b
$ (Located (IdGhcP p) -> Scope) -> [Located (IdGhcP p)] -> [Scope]
forall a b. (a -> b) -> [a] -> [b]
map Located (IdGhcP p) -> Scope
forall a. Located a -> Scope
mkLScope [Located (IdGhcP p)]
[Located (IdP (GhcPass p))]
args
(InfixCon Located (IdP (GhcPass p))
a Located (IdP (GhcPass p))
b) -> Scope -> Scope -> Scope
combineScopes (Located (IdGhcP p) -> Scope
forall a. Located a -> Scope
mkLScope Located (IdGhcP p)
Located (IdP (GhcPass p))
a) (Located (IdGhcP p) -> Scope
forall a. Located a -> Scope
mkLScope Located (IdGhcP p)
Located (IdP (GhcPass p))
b)
(RecCon [RecordPatSynField (Located (IdP (GhcPass p)))]
r) -> (RecordPatSynField (Located (IdGhcP p)) -> Scope -> Scope)
-> Scope -> [RecordPatSynField (Located (IdGhcP p))] -> Scope
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr RecordPatSynField (Located (IdGhcP p)) -> Scope -> Scope
forall {a}. RecordPatSynField (Located a) -> Scope -> Scope
go Scope
NoScope [RecordPatSynField (Located (IdGhcP p))]
[RecordPatSynField (Located (IdP (GhcPass p)))]
r
go :: RecordPatSynField (Located a) -> Scope -> Scope
go (RecordPatSynField Located a
a Located a
b) Scope
c = Scope -> Scope -> Scope
combineScopes Scope
c
(Scope -> Scope) -> Scope -> Scope
forall a b. (a -> b) -> a -> b
$ Scope -> Scope -> Scope
combineScopes (Located a -> Scope
forall a. Located a -> Scope
mkLScope Located a
a) (Located a -> Scope
forall a. Located a -> Scope
mkLScope Located a
b)
detSpan :: Maybe Span
detSpan = case Scope
detScope of
LocalScope Span
a -> Span -> Maybe Span
forall a. a -> Maybe a
Just Span
a
Scope
_ -> Maybe Span
forall a. Maybe a
Nothing
toBind :: HsConDetails
(Located (IdGhcP p)) [RecordPatSynField (Located (IdGhcP p))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
toBind (PrefixCon [Located (IdGhcP p)]
args) = [Context (Located (IdGhcP p))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall arg rec. [arg] -> HsConDetails arg rec
PrefixCon ([Context (Located (IdGhcP p))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))])
-> [Context (Located (IdGhcP p))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall a b. (a -> b) -> a -> b
$ (Located (IdGhcP p) -> Context (Located (IdGhcP p)))
-> [Located (IdGhcP p)] -> [Context (Located (IdGhcP p))]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located (IdGhcP p)]
args
toBind (InfixCon Located (IdGhcP p)
a Located (IdGhcP p)
b) = Context (Located (IdGhcP p))
-> Context (Located (IdGhcP p))
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall arg rec. arg -> arg -> HsConDetails arg rec
InfixCon (ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located (IdGhcP p)
a) (ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located (IdGhcP p)
b)
toBind (RecCon [RecordPatSynField (Located (IdGhcP p))]
r) = [PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall arg rec. rec -> HsConDetails arg rec
RecCon ([PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))])
-> [PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
-> HsConDetails
(Context (Located (IdGhcP p)))
[PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall a b. (a -> b) -> a -> b
$ (RecordPatSynField (Located (IdGhcP p))
-> PatSynFieldContext (RecordPatSynField (Located (IdGhcP p))))
-> [RecordPatSynField (Located (IdGhcP p))]
-> [PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Span
-> RecordPatSynField (Located (IdGhcP p))
-> PatSynFieldContext (RecordPatSynField (Located (IdGhcP p)))
forall a. Maybe Span -> a -> PatSynFieldContext a
PSC Maybe Span
detSpan) [RecordPatSynField (Located (IdGhcP p))]
r
instance HiePass p => ToHie (HsPatSynDir (GhcPass p)) where
toHie :: HsPatSynDir (GhcPass p) -> HieM [HieAST Type]
toHie HsPatSynDir (GhcPass p)
dir = case HsPatSynDir (GhcPass p)
dir of
ExplicitBidirectional MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg -> MatchGroup (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg
HsPatSynDir (GhcPass p)
_ -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ( HiePass p
, Data body
, ToHie (Located body)
) => ToHie (LMatch (GhcPass p) (Located body)) where
toHie :: LMatch (GhcPass p) (Located body) -> HieM [HieAST Type]
toHie (L SrcSpan
span Match (GhcPass p) (Located body)
m ) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HieM [HieAST Type]
node HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case Match (GhcPass p) (Located body)
m of
Match{m_ctxt :: forall p body. Match p body -> HsMatchContext (NoGhcTc p)
m_ctxt=HsMatchContext (NoGhcTc (GhcPass p))
mctx, m_pats :: forall p body. Match p body -> [LPat p]
m_pats = [LPat (GhcPass p)]
pats, m_grhss :: forall p body. Match p body -> GRHSs p body
m_grhss = GRHSs (GhcPass p) (Located body)
grhss } ->
[ HsMatchContext (GhcPass (NoGhcTcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsMatchContext (GhcPass (NoGhcTcPass p))
HsMatchContext (NoGhcTc (GhcPass p))
mctx
, let rhsScope :: Scope
rhsScope = SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ GRHSs (GhcPass p) (Located body) -> SrcSpan
forall p body. GRHSs p body -> SrcSpan
grhss_span GRHSs (GhcPass p) (Located body)
grhss
in [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type])
-> [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
forall a. Maybe a
Nothing Scope
rhsScope Scope
NoScope [LPat (GhcPass p)]
pats
, GRHSs (GhcPass p) (Located body) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GRHSs (GhcPass p) (Located body)
grhss
]
where
node :: HieM [HieAST Type]
node = case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc -> Match (GhcPass p) (Located body) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode Match (GhcPass p) (Located body)
m SrcSpan
span
HiePassEv p
HieRn -> Match (GhcPass p) (Located body) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode Match (GhcPass p) (Located body)
m SrcSpan
span
instance HiePass p => ToHie (HsMatchContext (GhcPass p)) where
toHie :: HsMatchContext (GhcPass p) -> HieM [HieAST Type]
toHie (FunRhs{mc_fun :: forall p. HsMatchContext p -> LIdP p
mc_fun=LIdP (GhcPass p)
name}) = Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
MatchBind Located (IdGhcP p)
LIdP (GhcPass p)
name
toHie (StmtCtxt HsStmtContext (GhcPass p)
a) = HsStmtContext (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsStmtContext (GhcPass p)
a
toHie HsMatchContext (GhcPass p)
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance HiePass p => ToHie (HsStmtContext (GhcPass p)) where
toHie :: HsStmtContext (GhcPass p) -> HieM [HieAST Type]
toHie (PatGuard HsMatchContext (GhcPass p)
a) = HsMatchContext (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsMatchContext (GhcPass p)
a
toHie (ParStmtCtxt HsStmtContext (GhcPass p)
a) = HsStmtContext (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsStmtContext (GhcPass p)
a
toHie (TransStmtCtxt HsStmtContext (GhcPass p)
a) = HsStmtContext (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsStmtContext (GhcPass p)
a
toHie HsStmtContext (GhcPass p)
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance HiePass p => ToHie (PScoped (Located (Pat (GhcPass p)))) where
toHie :: PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
toHie (PS Maybe Span
rsp Scope
scope Scope
pscope lpat :: Located (Pat (GhcPass p))
lpat@(L SrcSpan
ospan Pat (GhcPass p)
opat)) =
[HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Located (Pat (GhcPass p)) -> HieM [HieAST Type]
forall a. HasType a => a -> HieM [HieAST Type]
getTypeNode Located (Pat (GhcPass p))
lpat HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case Pat (GhcPass p)
opat of
WildPat XWildPat (GhcPass p)
_ ->
[]
VarPat XVarPat (GhcPass p)
_ Located (IdP (GhcPass p))
lname ->
[ Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (Scope -> Scope -> Maybe Span -> ContextInfo
PatternBind Scope
scope Scope
pscope Maybe Span
rsp) Located (IdGhcP p)
Located (IdP (GhcPass p))
lname
]
LazyPat XLazyPat (GhcPass p)
_ LPat (GhcPass p)
p ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
p
]
AsPat XAsPat (GhcPass p)
_ Located (IdP (GhcPass p))
lname LPat (GhcPass p)
pat ->
[ Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (Scope -> Scope -> Maybe Span -> ContextInfo
PatternBind Scope
scope
(Scope -> Scope -> Scope
combineScopes (Located (Pat (GhcPass p)) -> Scope
forall a. Located a -> Scope
mkLScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat) Scope
pscope)
Maybe Span
rsp)
Located (IdGhcP p)
Located (IdP (GhcPass p))
lname
, PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
ParPat XParPat (GhcPass p)
_ LPat (GhcPass p)
pat ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
BangPat XBangPat (GhcPass p)
_ LPat (GhcPass p)
pat ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
ListPat XListPat (GhcPass p)
_ [LPat (GhcPass p)]
pats ->
[ [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type])
-> [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
rsp Scope
scope Scope
pscope [LPat (GhcPass p)]
pats
]
TuplePat XTuplePat (GhcPass p)
_ [LPat (GhcPass p)]
pats Boxity
_ ->
[ [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type])
-> [PScoped (Located (Pat (GhcPass p)))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
rsp Scope
scope Scope
pscope [LPat (GhcPass p)]
pats
]
SumPat XSumPat (GhcPass p)
_ LPat (GhcPass p)
pat TypeIndex
_ TypeIndex
_ ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
ConPat {pat_con :: forall p. Pat p -> Located (ConLikeP p)
pat_con = Located (ConLikeP (GhcPass p))
con, pat_args :: forall p. Pat p -> HsConPatDetails p
pat_args = HsConPatDetails (GhcPass p)
dets, pat_con_ext :: forall p. Pat p -> XConPat p
pat_con_ext = XConPat (GhcPass p)
ext} ->
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use (Located Name -> Context (Located Name))
-> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ (ConLike -> Name) -> GenLocated SrcSpan ConLike -> Located Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ConLike -> Name
conLikeName GenLocated SrcSpan ConLike
Located (ConLikeP (GhcPass p))
con
, HsConDetails
(PScoped (Located (Pat GhcTc)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcTc)))))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (HsConDetails
(PScoped (Located (Pat GhcTc)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcTc)))))
-> HieM [HieAST Type])
-> HsConDetails
(PScoped (Located (Pat GhcTc)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcTc)))))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsConDetails
(Located (Pat GhcTc))
(HsRecFields (GhcPass p) (Located (Pat GhcTc)))
-> HsConDetails
(PScoped (Located (Pat GhcTc)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcTc)))))
forall a.
(a ~ LPat (GhcPass p)) =>
HsConDetails a (HsRecFields (GhcPass p) a)
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
contextify HsConDetails
(Located (Pat GhcTc))
(HsRecFields (GhcPass p) (Located (Pat GhcTc)))
HsConPatDetails (GhcPass p)
dets
, let ev_binds :: TcEvBinds
ev_binds = ConPatTc -> TcEvBinds
cpt_binds XConPat (GhcPass p)
ConPatTc
ext
ev_vars :: [Id]
ev_vars = ConPatTc -> [Id]
cpt_dicts XConPat (GhcPass p)
ConPatTc
ext
wrap :: HsWrapper
wrap = ConPatTc -> HsWrapper
cpt_wrap XConPat (GhcPass p)
ConPatTc
ext
evscope :: Scope
evscope = SrcSpan -> Scope
mkScope SrcSpan
ospan Scope -> Scope -> Scope
`combineScopes` Scope
scope Scope -> Scope -> Scope
`combineScopes` Scope
pscope
in [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM [ EvBindContext (GenLocated SrcSpan TcEvBinds) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type])
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> Maybe Span
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a. Scope -> Maybe Span -> a -> EvBindContext a
EvBindContext Scope
scope Maybe Span
rsp (GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds))
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan TcEvBinds
ev_binds
, Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Located HsWrapper -> HieM [HieAST Type])
-> Located HsWrapper -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan HsWrapper
wrap
, [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type])
-> [Context (GenLocated SrcSpan Id)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Id -> Context (GenLocated SrcSpan Id))
-> [Id] -> [Context (GenLocated SrcSpan Id)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind EvVarSource
EvPatternBind Scope
evscope Maybe Span
rsp)
(GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id))
-> (Id -> GenLocated SrcSpan Id)
-> Id
-> Context (GenLocated SrcSpan Id)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan) [Id]
ev_vars
]
]
HiePassEv p
HieRn ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (ConLikeP (GhcPass p))
con
, HsConDetails
(PScoped (Located (Pat GhcRn)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcRn)))))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (HsConDetails
(PScoped (Located (Pat GhcRn)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcRn)))))
-> HieM [HieAST Type])
-> HsConDetails
(PScoped (Located (Pat GhcRn)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcRn)))))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsConDetails
(Located (Pat GhcRn))
(HsRecFields (GhcPass p) (Located (Pat GhcRn)))
-> HsConDetails
(PScoped (Located (Pat GhcRn)))
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat GhcRn)))))
forall a.
(a ~ LPat (GhcPass p)) =>
HsConDetails a (HsRecFields (GhcPass p) a)
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
contextify HsConDetails
(Located (Pat GhcRn))
(HsRecFields (GhcPass p) (Located (Pat GhcRn)))
HsConPatDetails (GhcPass p)
dets
]
ViewPat XViewPat (GhcPass p)
_ LHsExpr (GhcPass p)
expr LPat (GhcPass p)
pat ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
SplicePat XSplicePat (GhcPass p)
_ HsSplice (GhcPass p)
sp ->
[ GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type])
-> GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> HsSplice (GhcPass p)
-> GenLocated SrcSpan (HsSplice (GhcPass p))
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan HsSplice (GhcPass p)
sp
]
LitPat XLitPat (GhcPass p)
_ HsLit (GhcPass p)
_ ->
[]
NPat XNPat (GhcPass p)
_ Located (HsOverLit (GhcPass p))
_ Maybe (SyntaxExpr (GhcPass p))
_ SyntaxExpr (GhcPass p)
_ ->
[]
NPlusKPat XNPlusKPat (GhcPass p)
_ Located (IdP (GhcPass p))
n Located (HsOverLit (GhcPass p))
_ HsOverLit (GhcPass p)
_ SyntaxExpr (GhcPass p)
_ SyntaxExpr (GhcPass p)
_ ->
[ Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located (IdGhcP p)) -> HieM [HieAST Type])
-> Context (Located (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located (IdGhcP p) -> Context (Located (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (Scope -> Scope -> Maybe Span -> ContextInfo
PatternBind Scope
scope Scope
pscope Maybe Span
rsp) Located (IdGhcP p)
Located (IdP (GhcPass p))
n
]
SigPat XSigPat (GhcPass p)
_ LPat (GhcPass p)
pat HsPatSigType (NoGhcTc (GhcPass p))
sig ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
, case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc ->
let cscope :: Scope
cscope = Located (Pat GhcTc) -> Scope
forall a. Located a -> Scope
mkLScope Located (Pat GhcTc)
LPat (GhcPass p)
pat in
TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type])
-> TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> HsPatSigType GhcRn -> TScoped (HsPatSigType GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [Scope
cscope, Scope
scope, Scope
pscope])
HsPatSigType GhcRn
HsPatSigType (NoGhcTc (GhcPass p))
sig
HiePassEv p
HieRn -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
]
XPat XXPat (GhcPass p)
e ->
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc ->
let CoPat HsWrapper
wrap Pat GhcTc
pat Type
_ = XXPat (GhcPass p)
CoPat
e
in [ Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Located HsWrapper -> HieM [HieAST Type])
-> Located HsWrapper -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan HsWrapper
wrap
, PScoped (Located (Pat GhcTc)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat GhcTc)) -> HieM [HieAST Type])
-> PScoped (Located (Pat GhcTc)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat GhcTc)
-> PScoped (Located (Pat GhcTc))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
pscope (Located (Pat GhcTc) -> PScoped (Located (Pat GhcTc)))
-> Located (Pat GhcTc) -> PScoped (Located (Pat GhcTc))
forall a b. (a -> b) -> a -> b
$ (SrcSpan -> Pat GhcTc -> Located (Pat GhcTc)
forall l e. l -> e -> GenLocated l e
L SrcSpan
ospan Pat GhcTc
pat)
]
#if __GLASGOW_HASKELL__ < 811
HieRn -> []
#endif
where
contextify :: a ~ LPat (GhcPass p) => HsConDetails a (HsRecFields (GhcPass p) a)
-> HsConDetails (PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
contextify :: forall a.
(a ~ LPat (GhcPass p)) =>
HsConDetails a (HsRecFields (GhcPass p) a)
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
contextify (PrefixCon [a]
args) = [PScoped a]
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
forall arg rec. [arg] -> HsConDetails arg rec
PrefixCon ([PScoped a]
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a))))
-> [PScoped a]
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
rsp Scope
scope Scope
pscope [a]
[LPat (GhcPass p)]
args
contextify (InfixCon a
a a
b) = PScoped a
-> PScoped a
-> HsConDetails
(PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
forall arg rec. arg -> arg -> HsConDetails arg rec
InfixCon PScoped a
a' PScoped a
b'
where [PScoped a
a', PScoped a
b'] = Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
forall (p :: Pass).
Maybe Span
-> Scope
-> Scope
-> [LPat (GhcPass p)]
-> [PScoped (LPat (GhcPass p))]
patScopes Maybe Span
rsp Scope
scope Scope
pscope [a
LPat (GhcPass p)
a,a
LPat (GhcPass p)
b]
contextify (RecCon HsRecFields (GhcPass p) a
r) = RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
-> HsConDetails
(PScoped a)
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))))
forall arg rec. rec -> HsConDetails arg rec
RecCon (RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
-> HsConDetails
(PScoped a)
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))))
-> RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
-> HsConDetails
(PScoped a)
(RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))))
forall a b. (a -> b) -> a -> b
$ RecFieldContext
-> HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
-> RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
forall a. RecFieldContext -> a -> RContext a
RC RecFieldContext
RecFieldMatch (HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
-> RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))))
-> HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
-> RContext
(HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
forall a b. (a -> b) -> a -> b
$ HsRecFields (GhcPass p) (Located (Pat (GhcPass p)))
-> HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
contextify_rec HsRecFields (GhcPass p) a
HsRecFields (GhcPass p) (Located (Pat (GhcPass p)))
r
contextify_rec :: HsRecFields (GhcPass p) (Located (Pat (GhcPass p)))
-> HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
contextify_rec (HsRecFields [LHsRecField (GhcPass p) (Located (Pat (GhcPass p)))]
fds Maybe (Located TypeIndex)
a) = [LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))]
-> Maybe (Located TypeIndex)
-> HsRecFields (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
forall p arg.
[LHsRecField p arg]
-> Maybe (Located TypeIndex) -> HsRecFields p arg
HsRecFields ((RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
-> [RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))]
-> [LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))]
forall a b. (a -> b) -> [a] -> [b]
map RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
go [RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))]
scoped_fds) Maybe (Located TypeIndex)
a
where
go :: RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
go (RS Scope
fscope (L SrcSpan
spn (HsRecField Located (FieldOcc (GhcPass p))
lbl Located (Pat (GhcPass p))
pat Bool
pun))) =
SrcSpan
-> HsRecField'
(FieldOcc (GhcPass p)) (PScoped (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
forall l e. l -> e -> GenLocated l e
L SrcSpan
spn (HsRecField'
(FieldOcc (GhcPass p)) (PScoped (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p)))))
-> HsRecField'
(FieldOcc (GhcPass p)) (PScoped (Located (Pat (GhcPass p))))
-> LHsRecField (GhcPass p) (PScoped (Located (Pat (GhcPass p))))
forall a b. (a -> b) -> a -> b
$ Located (FieldOcc (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
-> Bool
-> HsRecField'
(FieldOcc (GhcPass p)) (PScoped (Located (Pat (GhcPass p))))
forall id arg. Located id -> arg -> Bool -> HsRecField' id arg
HsRecField Located (FieldOcc (GhcPass p))
lbl (Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
rsp Scope
scope Scope
fscope Located (Pat (GhcPass p))
pat) Bool
pun
scoped_fds :: [RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))]
scoped_fds = Scope
-> [LHsRecField (GhcPass p) (Located (Pat (GhcPass p)))]
-> [RScoped (LHsRecField (GhcPass p) (Located (Pat (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
pscope [LHsRecField (GhcPass p) (Located (Pat (GhcPass p)))]
fds
instance ToHie (TScoped (HsPatSigType GhcRn)) where
toHie :: TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]
toHie (TS TyVarScope
sc (HsPS (HsPSRn [Name]
wcs [Name]
tvs) body :: GenLocated SrcSpan (HsType GhcRn)
body@(L SrcSpan
span HsType GhcRn
_))) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ [Context Name] -> HieM [HieAST Type]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly ([Context Name] -> HieM [HieAST Type])
-> [Context Name] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Name -> Context Name) -> [Name] -> [Context Name]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Name -> Context Name
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Name -> Context Name)
-> ContextInfo -> Name -> Context Name
forall a b. (a -> b) -> a -> b
$ Scope -> TyVarScope -> ContextInfo
TyVarBind (SrcSpan -> Scope
mkScope SrcSpan
span) TyVarScope
sc) ([Name]
wcs[Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++[Name]
tvs)
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
body
]
instance ( ToHie (Located body)
, HiePass p
, Data body
) => ToHie (GRHSs (GhcPass p) (Located body)) where
toHie :: GRHSs (GhcPass p) (Located body) -> HieM [HieAST Type]
toHie GRHSs (GhcPass p) (Located body)
grhs = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case GRHSs (GhcPass p) (Located body)
grhs of
GRHSs XCGRHSs (GhcPass p) (Located body)
_ [LGRHS (GhcPass p) (Located body)]
grhss LHsLocalBinds (GhcPass p)
binds ->
[ [LGRHS (GhcPass p) (Located body)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LGRHS (GhcPass p) (Located body)]
grhss
, RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type])
-> RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> LHsLocalBinds (GhcPass p) -> RScoped (LHsLocalBinds (GhcPass p))
forall a. Scope -> a -> RScoped a
RS (SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ GRHSs (GhcPass p) (Located body) -> SrcSpan
forall p body. GRHSs p body -> SrcSpan
grhss_span GRHSs (GhcPass p) (Located body)
grhs) LHsLocalBinds (GhcPass p)
binds
]
instance ( ToHie (Located body)
, HiePass a
, Data body
) => ToHie (LGRHS (GhcPass a) (Located body)) where
toHie :: LGRHS (GhcPass a) (Located body) -> HieM [HieAST Type]
toHie (L SrcSpan
span GRHS (GhcPass a) (Located body)
g) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HieM [HieAST Type]
node HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case GRHS (GhcPass a) (Located body)
g of
GRHS XCGRHS (GhcPass a) (Located body)
_ [Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a)))]
guards Located body
body ->
[ [RScoped
(Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a)))]
-> [RScoped
(Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes (Located body -> Scope
forall a. Located a -> Scope
mkLScope Located body
body) [Located (StmtLR (GhcPass a) (GhcPass a) (LHsExpr (GhcPass a)))]
guards
, Located body -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located body
body
]
where
node :: HieM [HieAST Type]
node = case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @a of
HiePassEv a
HieRn -> GRHS (GhcPass a) (Located body) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode GRHS (GhcPass a) (Located body)
g SrcSpan
span
HiePassEv a
HieTc -> GRHS (GhcPass a) (Located body) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode GRHS (GhcPass a) (Located body)
g SrcSpan
span
instance HiePass p => ToHie (LHsExpr (GhcPass p)) where
toHie :: LHsExpr (GhcPass p) -> HieM [HieAST Type]
toHie e :: LHsExpr (GhcPass p)
e@(L SrcSpan
mspan HsExpr (GhcPass p)
oexpr) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. HasType a => a -> HieM [HieAST Type]
getTypeNode LHsExpr (GhcPass p)
e HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsExpr (GhcPass p)
oexpr of
HsVar XVar (GhcPass p)
_ (L SrcSpan
_ IdP (GhcPass p)
var) ->
[ Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan (IdGhcP p)
-> Context (GenLocated SrcSpan (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use (SrcSpan -> IdGhcP p -> GenLocated SrcSpan (IdGhcP p)
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan IdGhcP p
IdP (GhcPass p)
var)
]
HsUnboundVar XUnboundVar (GhcPass p)
_ OccName
_ ->
[]
HsConLikeOut XConLikeOut (GhcPass p)
_ ConLike
con ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use (Located Name -> Context (Located Name))
-> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan (Name -> Located Name) -> Name -> Located Name
forall a b. (a -> b) -> a -> b
$ ConLike -> Name
conLikeName ConLike
con
]
HsRecFld XRecFld (GhcPass p)
_ AmbiguousFieldOcc (GhcPass p)
fld ->
[ RFContext (GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RFContext (GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p)))
-> HieM [HieAST Type])
-> RFContext (GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RecFieldContext
-> Maybe Span
-> GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p))
-> RFContext (GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p)))
forall a. RecFieldContext -> Maybe Span -> a -> RFContext a
RFC RecFieldContext
RecFieldOcc Maybe Span
forall a. Maybe a
Nothing (SrcSpan
-> AmbiguousFieldOcc (GhcPass p)
-> GenLocated SrcSpan (AmbiguousFieldOcc (GhcPass p))
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan AmbiguousFieldOcc (GhcPass p)
fld)
]
HsOverLabel XOverLabel (GhcPass p)
_ Maybe (IdP (GhcPass p))
_ FastString
_ -> []
HsIPVar XIPVar (GhcPass p)
_ HsIPName
_ -> []
HsOverLit XOverLitE (GhcPass p)
_ HsOverLit (GhcPass p)
_ -> []
HsLit XLitE (GhcPass p)
_ HsLit (GhcPass p)
_ -> []
HsLam XLam (GhcPass p)
_ MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg ->
[ MatchGroup (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg
]
HsLamCase XLamCase (GhcPass p)
_ MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg ->
[ MatchGroup (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
mg
]
HsApp XApp (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
]
HsAppType XAppTypeE (GhcPass p)
_ LHsExpr (GhcPass p)
expr LHsWcType (NoGhcTc (GhcPass p))
sig ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, TScoped (LHsWcType (GhcPass (NoGhcTcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsWcType (GhcPass (NoGhcTcPass p)))
-> HieM [HieAST Type])
-> TScoped (LHsWcType (GhcPass (NoGhcTcPass p)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsWcType (GhcPass (NoGhcTcPass p))
-> TScoped (LHsWcType (GhcPass (NoGhcTcPass p)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) LHsWcType (GhcPass (NoGhcTcPass p))
LHsWcType (NoGhcTc (GhcPass p))
sig
]
OpApp XOpApp (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b LHsExpr (GhcPass p)
c ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
c
]
NegApp XNegApp (GhcPass p)
_ LHsExpr (GhcPass p)
a SyntaxExpr (GhcPass p)
_ ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
]
HsPar XPar (GhcPass p)
_ LHsExpr (GhcPass p)
a ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
]
SectionL XSectionL (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
]
SectionR XSectionR (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
]
ExplicitTuple XExplicitTuple (GhcPass p)
_ [LHsTupArg (GhcPass p)]
args Boxity
_ ->
[ [LHsTupArg (GhcPass p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LHsTupArg (GhcPass p)]
args
]
ExplicitSum XExplicitSum (GhcPass p)
_ TypeIndex
_ TypeIndex
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsCase XCase (GhcPass p)
_ LHsExpr (GhcPass p)
expr MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
matches ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, MatchGroup (GhcPass p) (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsExpr (GhcPass p))
matches
]
HsIf XIf (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b LHsExpr (GhcPass p)
c ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
c
]
HsMultiIf XMultiIf (GhcPass p)
_ [LGRHS (GhcPass p) (LHsExpr (GhcPass p))]
grhss ->
[ [LGRHS (GhcPass p) (LHsExpr (GhcPass p))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LGRHS (GhcPass p) (LHsExpr (GhcPass p))]
grhss
]
HsLet XLet (GhcPass p)
_ LHsLocalBinds (GhcPass p)
binds LHsExpr (GhcPass p)
expr ->
[ RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type])
-> RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> LHsLocalBinds (GhcPass p) -> RScoped (LHsLocalBinds (GhcPass p))
forall a. Scope -> a -> RScoped a
RS (LHsExpr (GhcPass p) -> Scope
forall a. Located a -> Scope
mkLScope LHsExpr (GhcPass p)
expr) LHsLocalBinds (GhcPass p)
binds
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsDo XDo (GhcPass p)
_ HsStmtContext GhcRn
_ (L SrcSpan
ispan [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts) ->
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
ispan
, [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
NoScope [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts
]
ExplicitList XExplicitList (GhcPass p)
_ Maybe (SyntaxExpr (GhcPass p))
_ [LHsExpr (GhcPass p)]
exprs ->
[ [LHsExpr (GhcPass p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LHsExpr (GhcPass p)]
exprs
]
RecordCon {rcon_ext :: forall p. HsExpr p -> XRecordCon p
rcon_ext = XRecordCon (GhcPass p)
mrealcon, rcon_con_name :: forall p. HsExpr p -> Located (IdP p)
rcon_con_name = GenLocated SrcSpan (IdP (GhcPass p))
name, rcon_flds :: forall p. HsExpr p -> HsRecordBinds p
rcon_flds = HsRecordBinds (GhcPass p)
binds} ->
[ Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan (IdGhcP p)
-> Context (GenLocated SrcSpan (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use (forall p.
HasRealDataConName p =>
XRecordCon p -> Located (IdP p) -> Located (IdP p)
getRealDataCon @(GhcPass p) XRecordCon (GhcPass p)
mrealcon GenLocated SrcSpan (IdP (GhcPass p))
name)
, RContext (HsRecordBinds (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RContext (HsRecordBinds (GhcPass p)) -> HieM [HieAST Type])
-> RContext (HsRecordBinds (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RecFieldContext
-> HsRecordBinds (GhcPass p)
-> RContext (HsRecordBinds (GhcPass p))
forall a. RecFieldContext -> a -> RContext a
RC RecFieldContext
RecFieldAssign (HsRecordBinds (GhcPass p) -> RContext (HsRecordBinds (GhcPass p)))
-> HsRecordBinds (GhcPass p)
-> RContext (HsRecordBinds (GhcPass p))
forall a b. (a -> b) -> a -> b
$ HsRecordBinds (GhcPass p)
binds
]
RecordUpd {rupd_expr :: forall p. HsExpr p -> LHsExpr p
rupd_expr = LHsExpr (GhcPass p)
expr, rupd_flds :: forall p. HsExpr p -> [LHsRecUpdField p]
rupd_flds = [LHsRecUpdField (GhcPass p)]
upds}->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, [RContext (LHsRecUpdField (GhcPass p))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RContext (LHsRecUpdField (GhcPass p))] -> HieM [HieAST Type])
-> [RContext (LHsRecUpdField (GhcPass p))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsRecUpdField (GhcPass p)
-> RContext (LHsRecUpdField (GhcPass p)))
-> [LHsRecUpdField (GhcPass p)]
-> [RContext (LHsRecUpdField (GhcPass p))]
forall a b. (a -> b) -> [a] -> [b]
map (RecFieldContext
-> LHsRecUpdField (GhcPass p)
-> RContext (LHsRecUpdField (GhcPass p))
forall a. RecFieldContext -> a -> RContext a
RC RecFieldContext
RecFieldAssign) [LHsRecUpdField (GhcPass p)]
upds
]
ExprWithTySig XExprWithTySig (GhcPass p)
_ LHsExpr (GhcPass p)
expr LHsSigWcType (NoGhcTc (GhcPass p))
sig ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, TScoped (LHsSigWcType (GhcPass (NoGhcTcPass p)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigWcType (GhcPass (NoGhcTcPass p)))
-> HieM [HieAST Type])
-> TScoped (LHsSigWcType (GhcPass (NoGhcTcPass p)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsSigWcType (GhcPass (NoGhcTcPass p))
-> TScoped (LHsSigWcType (GhcPass (NoGhcTcPass p)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [LHsExpr (GhcPass p) -> Scope
forall a. Located a -> Scope
mkLScope LHsExpr (GhcPass p)
expr]) LHsSigWcType (GhcPass (NoGhcTcPass p))
LHsSigWcType (NoGhcTc (GhcPass p))
sig
]
ArithSeq XArithSeq (GhcPass p)
_ Maybe (SyntaxExpr (GhcPass p))
_ ArithSeqInfo (GhcPass p)
info ->
[ ArithSeqInfo (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ArithSeqInfo (GhcPass p)
info
]
HsPragE XPragE (GhcPass p)
_ HsPragE (GhcPass p)
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsProc XProc (GhcPass p)
_ LPat (GhcPass p)
pat LHsCmdTop (GhcPass p)
cmdtop ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
forall a. Maybe a
Nothing (LHsCmdTop (GhcPass p) -> Scope
forall a. Located a -> Scope
mkLScope LHsCmdTop (GhcPass p)
cmdtop) Scope
NoScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
, LHsCmdTop (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmdTop (GhcPass p)
cmdtop
]
HsStatic XStatic (GhcPass p)
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsTick XTick (GhcPass p)
_ Tickish (IdP (GhcPass p))
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsBinTick XBinTick (GhcPass p)
_ TypeIndex
_ TypeIndex
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsBracket XBracket (GhcPass p)
_ HsBracket (GhcPass p)
b ->
[ HsBracket (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsBracket (GhcPass p)
b
]
HsRnBracketOut XRnBracketOut (GhcPass p)
_ HsBracket GhcRn
b [PendingRnSplice]
p ->
[ HsBracket GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsBracket GhcRn
b
, [PendingRnSplice] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [PendingRnSplice]
p
]
HsTcBracketOut XTcBracketOut (GhcPass p)
_ Maybe QuoteWrapper
_wrap HsBracket GhcRn
b [PendingTcSplice]
p ->
[ HsBracket GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsBracket GhcRn
b
, [PendingTcSplice] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [PendingTcSplice]
p
]
HsSpliceE XSpliceE (GhcPass p)
_ HsSplice (GhcPass p)
x ->
[ GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type])
-> GenLocated SrcSpan (HsSplice (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> HsSplice (GhcPass p)
-> GenLocated SrcSpan (HsSplice (GhcPass p))
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan HsSplice (GhcPass p)
x
]
XExpr XXExpr (GhcPass p)
x
| GhcPass p
GhcTc <- forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p
, WrapExpr (HsWrap HsWrapper
w HsExpr GhcTc
a) <- XXExpr (GhcPass p)
x
-> [ LHsExpr GhcTc -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (LHsExpr GhcTc -> HieM [HieAST Type])
-> LHsExpr GhcTc -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsExpr GhcTc -> LHsExpr GhcTc
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan HsExpr GhcTc
a
, Located HsWrapper -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsWrapper -> Located HsWrapper
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan HsWrapper
w)
]
| GhcPass p
GhcTc <- forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p
, ExpansionExpr (HsExpanded HsExpr GhcRn
_ HsExpr GhcTc
b) <- XXExpr (GhcPass p)
x
-> [ LHsExpr GhcTc -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan -> HsExpr GhcTc -> LHsExpr GhcTc
forall l e. l -> e -> GenLocated l e
L SrcSpan
mspan HsExpr GhcTc
b)
]
| Bool
otherwise -> []
instance HiePass p => ToHie (LHsTupArg (GhcPass p)) where
toHie :: LHsTupArg (GhcPass p) -> HieM [HieAST Type]
toHie (L SrcSpan
span HsTupArg (GhcPass p)
arg) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsTupArg (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsTupArg (GhcPass p)
arg SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsTupArg (GhcPass p)
arg of
Present XPresent (GhcPass p)
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
Missing XMissing (GhcPass p)
_ -> []
instance ( ToHie (Located body)
, Data body
, HiePass p
) => ToHie (RScoped (LStmt (GhcPass p) (Located body))) where
toHie :: RScoped (LStmt (GhcPass p) (Located body)) -> HieM [HieAST Type]
toHie (RS Scope
scope (L SrcSpan
span StmtLR (GhcPass p) (GhcPass p) (Located body)
stmt)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HieM [HieAST Type]
node HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case StmtLR (GhcPass p) (GhcPass p) (Located body)
stmt of
LastStmt XLastStmt (GhcPass p) (GhcPass p) (Located body)
_ Located body
body Maybe Bool
_ SyntaxExpr (GhcPass p)
_ ->
[ Located body -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located body
body
]
BindStmt XBindStmt (GhcPass p) (GhcPass p) (Located body)
_ LPat (GhcPass p)
pat Located body
body ->
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS (SrcSpan -> Maybe Span
getRealSpan (SrcSpan -> Maybe Span) -> SrcSpan -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Located body -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located body
body) Scope
scope Scope
NoScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
, Located body -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located body
body
]
ApplicativeStmt XApplicativeStmt (GhcPass p) (GhcPass p) (Located body)
_ [(SyntaxExpr (GhcPass p), ApplicativeArg (GhcPass p))]
stmts Maybe (SyntaxExpr (GhcPass p))
_ ->
[ ((SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> HieM [HieAST Type])
-> [(SyntaxExprGhc p, ApplicativeArg (GhcPass p))]
-> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (RScoped (ApplicativeArg (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (ApplicativeArg (GhcPass p)) -> HieM [HieAST Type])
-> ((SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> RScoped (ApplicativeArg (GhcPass p)))
-> (SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scope
-> ApplicativeArg (GhcPass p)
-> RScoped (ApplicativeArg (GhcPass p))
forall a. Scope -> a -> RScoped a
RS Scope
scope (ApplicativeArg (GhcPass p)
-> RScoped (ApplicativeArg (GhcPass p)))
-> ((SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> ApplicativeArg (GhcPass p))
-> (SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> RScoped (ApplicativeArg (GhcPass p))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SyntaxExprGhc p, ApplicativeArg (GhcPass p))
-> ApplicativeArg (GhcPass p)
forall a b. (a, b) -> b
snd) [(SyntaxExpr (GhcPass p), ApplicativeArg (GhcPass p))]
[(SyntaxExprGhc p, ApplicativeArg (GhcPass p))]
stmts
]
BodyStmt XBodyStmt (GhcPass p) (GhcPass p) (Located body)
_ Located body
body SyntaxExpr (GhcPass p)
_ SyntaxExpr (GhcPass p)
_ ->
[ Located body -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located body
body
]
LetStmt XLetStmt (GhcPass p) (GhcPass p) (Located body)
_ LHsLocalBindsLR (GhcPass p) (GhcPass p)
binds ->
[ RScoped (LHsLocalBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (LHsLocalBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type])
-> RScoped (LHsLocalBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> LHsLocalBindsLR (GhcPass p) (GhcPass p)
-> RScoped (LHsLocalBindsLR (GhcPass p) (GhcPass p))
forall a. Scope -> a -> RScoped a
RS Scope
scope LHsLocalBindsLR (GhcPass p) (GhcPass p)
binds
]
ParStmt XParStmt (GhcPass p) (GhcPass p) (Located body)
_ [ParStmtBlock (GhcPass p) (GhcPass p)]
parstmts HsExpr (GhcPass p)
_ SyntaxExpr (GhcPass p)
_ ->
[ (ParStmtBlock (GhcPass p) (GhcPass p) -> HieM [HieAST Type])
-> [ParStmtBlock (GhcPass p) (GhcPass p)] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (\(ParStmtBlock XParStmtBlock (GhcPass p) (GhcPass p)
_ [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts [IdP (GhcPass p)]
_ SyntaxExpr (GhcPass p)
_) ->
[RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
NoScope [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts)
[ParStmtBlock (GhcPass p) (GhcPass p)]
parstmts
]
TransStmt {trS_stmts :: forall idL idR body. StmtLR idL idR body -> [ExprLStmt idL]
trS_stmts = [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts, trS_using :: forall idL idR body. StmtLR idL idR body -> LHsExpr idR
trS_using = LHsExpr (GhcPass p)
using, trS_by :: forall idL idR body. StmtLR idL idR body -> Maybe (LHsExpr idR)
trS_by = Maybe (LHsExpr (GhcPass p))
by} ->
[ [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
scope [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
using
, Maybe (LHsExpr (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LHsExpr (GhcPass p))
by
]
RecStmt {recS_stmts :: forall idL idR body. StmtLR idL idR body -> [LStmtLR idL idR body]
recS_stmts = [LStmt (GhcPass p) (Located body)]
stmts} ->
[ [RScoped (LStmt (GhcPass p) (Located body))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped (LStmt (GhcPass p) (Located body))]
-> HieM [HieAST Type])
-> [RScoped (LStmt (GhcPass p) (Located body))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LStmt (GhcPass p) (Located body)
-> RScoped (LStmt (GhcPass p) (Located body)))
-> [LStmt (GhcPass p) (Located body)]
-> [RScoped (LStmt (GhcPass p) (Located body))]
forall a b. (a -> b) -> [a] -> [b]
map (Scope
-> LStmt (GhcPass p) (Located body)
-> RScoped (LStmt (GhcPass p) (Located body))
forall a. Scope -> a -> RScoped a
RS (Scope
-> LStmt (GhcPass p) (Located body)
-> RScoped (LStmt (GhcPass p) (Located body)))
-> Scope
-> LStmt (GhcPass p) (Located body)
-> RScoped (LStmt (GhcPass p) (Located body))
forall a b. (a -> b) -> a -> b
$ Scope -> Scope -> Scope
combineScopes Scope
scope (SrcSpan -> Scope
mkScope SrcSpan
span)) [LStmt (GhcPass p) (Located body)]
stmts
]
where
node :: HieM [HieAST Type]
node = case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc -> StmtLR (GhcPass p) (GhcPass p) (Located body)
-> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode StmtLR (GhcPass p) (GhcPass p) (Located body)
stmt SrcSpan
span
HiePassEv p
HieRn -> StmtLR (GhcPass p) (GhcPass p) (Located body)
-> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode StmtLR (GhcPass p) (GhcPass p) (Located body)
stmt SrcSpan
span
instance HiePass p => ToHie (RScoped (LHsLocalBinds (GhcPass p))) where
toHie :: RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
toHie (RS Scope
scope (L SrcSpan
sp HsLocalBinds (GhcPass p)
binds)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsLocalBinds (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsLocalBinds (GhcPass p)
binds SrcSpan
sp HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsLocalBinds (GhcPass p)
binds of
EmptyLocalBinds XEmptyLocalBinds (GhcPass p) (GhcPass p)
_ -> []
HsIPBinds XHsIPBinds (GhcPass p) (GhcPass p)
_ HsIPBinds (GhcPass p)
ipbinds -> case HsIPBinds (GhcPass p)
ipbinds of
IPBinds XIPBinds (GhcPass p)
evbinds [LIPBind (GhcPass p)]
xs -> let sc :: Scope
sc = Scope -> Scope -> Scope
combineScopes Scope
scope (Scope -> Scope) -> Scope -> Scope
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Scope
mkScope SrcSpan
sp in
[ case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc -> EvBindContext (GenLocated SrcSpan TcEvBinds) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type])
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> Maybe Span
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a. Scope -> Maybe Span -> a -> EvBindContext a
EvBindContext Scope
sc (SrcSpan -> Maybe Span
getRealSpan SrcSpan
sp) (GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds))
-> GenLocated SrcSpan TcEvBinds
-> EvBindContext (GenLocated SrcSpan TcEvBinds)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> TcEvBinds -> GenLocated SrcSpan TcEvBinds
forall l e. l -> e -> GenLocated l e
L SrcSpan
sp XIPBinds (GhcPass p)
TcEvBinds
evbinds
HiePassEv p
HieRn -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
, [RScoped (LIPBind (GhcPass p))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped (LIPBind (GhcPass p))] -> HieM [HieAST Type])
-> [RScoped (LIPBind (GhcPass p))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LIPBind (GhcPass p) -> RScoped (LIPBind (GhcPass p)))
-> [LIPBind (GhcPass p)] -> [RScoped (LIPBind (GhcPass p))]
forall a b. (a -> b) -> [a] -> [b]
map (Scope -> LIPBind (GhcPass p) -> RScoped (LIPBind (GhcPass p))
forall a. Scope -> a -> RScoped a
RS Scope
sc) [LIPBind (GhcPass p)]
xs
]
HsValBinds XHsValBinds (GhcPass p) (GhcPass p)
_ HsValBindsLR (GhcPass p) (GhcPass p)
valBinds ->
[ RScoped (HsValBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (HsValBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type])
-> RScoped (HsValBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> HsValBindsLR (GhcPass p) (GhcPass p)
-> RScoped (HsValBindsLR (GhcPass p) (GhcPass p))
forall a. Scope -> a -> RScoped a
RS (Scope -> Scope -> Scope
combineScopes Scope
scope (Scope -> Scope) -> Scope -> Scope
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Scope
mkScope SrcSpan
sp)
HsValBindsLR (GhcPass p) (GhcPass p)
valBinds
]
instance HiePass p => ToHie (RScoped (LIPBind (GhcPass p))) where
toHie :: RScoped (LIPBind (GhcPass p)) -> HieM [HieAST Type]
toHie (RS Scope
scope (L SrcSpan
sp IPBind (GhcPass p)
bind)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IPBind (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode IPBind (GhcPass p)
bind SrcSpan
sp HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case IPBind (GhcPass p)
bind of
IPBind XCIPBind (GhcPass p)
_ (Left Located HsIPName
_) LHsExpr (GhcPass p)
expr -> [LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr]
IPBind XCIPBind (GhcPass p)
_ (Right IdP (GhcPass p)
v) LHsExpr (GhcPass p)
expr ->
[ Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan (IdGhcP p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan (IdGhcP p)
-> Context (GenLocated SrcSpan (IdGhcP p))
forall a. ContextInfo -> a -> Context a
C (EvVarSource -> Scope -> Maybe Span -> ContextInfo
EvidenceVarBind EvVarSource
EvImplicitBind Scope
scope (SrcSpan -> Maybe Span
getRealSpan SrcSpan
sp))
(GenLocated SrcSpan (IdGhcP p)
-> Context (GenLocated SrcSpan (IdGhcP p)))
-> GenLocated SrcSpan (IdGhcP p)
-> Context (GenLocated SrcSpan (IdGhcP p))
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IdGhcP p -> GenLocated SrcSpan (IdGhcP p)
forall l e. l -> e -> GenLocated l e
L SrcSpan
sp IdGhcP p
IdP (GhcPass p)
v
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
instance HiePass p => ToHie (RScoped (HsValBindsLR (GhcPass p) (GhcPass p))) where
toHie :: RScoped (HsValBindsLR (GhcPass p) (GhcPass p))
-> HieM [HieAST Type]
toHie (RS Scope
sc HsValBindsLR (GhcPass p) (GhcPass p)
v) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case HsValBindsLR (GhcPass p) (GhcPass p)
v of
ValBinds XValBinds (GhcPass p) (GhcPass p)
_ LHsBindsLR (GhcPass p) (GhcPass p)
binds [LSig (GhcPass p)]
sigs ->
[ Bag (BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Bag (BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
-> HieM [HieAST Type])
-> Bag (BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsBindLR (GhcPass p) (GhcPass p)
-> BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
-> LHsBindsLR (GhcPass p) (GhcPass p)
-> Bag (BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BindType
-> Scope
-> LHsBindLR (GhcPass p) (GhcPass p)
-> BindContext (LHsBindLR (GhcPass p) (GhcPass p))
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
RegularBind Scope
sc) LHsBindsLR (GhcPass p) (GhcPass p)
binds
, [SigContext (LSig (GhcPass p))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([SigContext (LSig (GhcPass p))] -> HieM [HieAST Type])
-> [SigContext (LSig (GhcPass p))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LSig (GhcPass p) -> SigContext (LSig (GhcPass p)))
-> [LSig (GhcPass p)] -> [SigContext (LSig (GhcPass p))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SigInfo -> LSig (GhcPass p) -> SigContext (LSig (GhcPass p))
forall a. SigInfo -> a -> SigContext a
SC (SigType -> Maybe Span -> SigInfo
SI SigType
BindSig Maybe Span
forall a. Maybe a
Nothing)) [LSig (GhcPass p)]
sigs
]
XValBindsLR XXValBindsLR (GhcPass p) (GhcPass p)
x -> [ RScoped (NHsValBindsLR (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (NHsValBindsLR (GhcPass p)) -> HieM [HieAST Type])
-> RScoped (NHsValBindsLR (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> NHsValBindsLR (GhcPass p) -> RScoped (NHsValBindsLR (GhcPass p))
forall a. Scope -> a -> RScoped a
RS Scope
sc XXValBindsLR (GhcPass p) (GhcPass p)
NHsValBindsLR (GhcPass p)
x ]
instance HiePass p => ToHie (RScoped (NHsValBindsLR (GhcPass p))) where
toHie :: RScoped (NHsValBindsLR (GhcPass p)) -> HieM [HieAST Type]
toHie (RS Scope
sc (NValBinds [(RecFlag, LHsBinds (GhcPass p))]
binds [LSig GhcRn]
sigs)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ [BindContext (LHsBindLR (GhcPass p) (GhcPass p))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (((RecFlag, LHsBinds (GhcPass p))
-> [BindContext (LHsBindLR (GhcPass p) (GhcPass p))])
-> [(RecFlag, LHsBinds (GhcPass p))]
-> [BindContext (LHsBindLR (GhcPass p) (GhcPass p))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((LHsBindLR (GhcPass p) (GhcPass p)
-> BindContext (LHsBindLR (GhcPass p) (GhcPass p)))
-> [LHsBindLR (GhcPass p) (GhcPass p)]
-> [BindContext (LHsBindLR (GhcPass p) (GhcPass p))]
forall a b. (a -> b) -> [a] -> [b]
map (BindType
-> Scope
-> LHsBindLR (GhcPass p) (GhcPass p)
-> BindContext (LHsBindLR (GhcPass p) (GhcPass p))
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
RegularBind Scope
sc) ([LHsBindLR (GhcPass p) (GhcPass p)]
-> [BindContext (LHsBindLR (GhcPass p) (GhcPass p))])
-> ((RecFlag, LHsBinds (GhcPass p))
-> [LHsBindLR (GhcPass p) (GhcPass p)])
-> (RecFlag, LHsBinds (GhcPass p))
-> [BindContext (LHsBindLR (GhcPass p) (GhcPass p))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LHsBinds (GhcPass p) -> [LHsBindLR (GhcPass p) (GhcPass p)]
forall a. Bag a -> [a]
bagToList (LHsBinds (GhcPass p) -> [LHsBindLR (GhcPass p) (GhcPass p)])
-> ((RecFlag, LHsBinds (GhcPass p)) -> LHsBinds (GhcPass p))
-> (RecFlag, LHsBinds (GhcPass p))
-> [LHsBindLR (GhcPass p) (GhcPass p)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RecFlag, LHsBinds (GhcPass p)) -> LHsBinds (GhcPass p)
forall a b. (a, b) -> b
snd) [(RecFlag, LHsBinds (GhcPass p))]
binds)
, [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([SigContext (LSig GhcRn)] -> HieM [HieAST Type])
-> [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LSig GhcRn -> SigContext (LSig GhcRn))
-> [LSig GhcRn] -> [SigContext (LSig GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn)
forall a. SigInfo -> a -> SigContext a
SC (SigType -> Maybe Span -> SigInfo
SI SigType
BindSig Maybe Span
forall a. Maybe a
Nothing)) [LSig GhcRn]
sigs
]
instance ( ToHie arg , HasLoc arg , Data arg
, HiePass p ) => ToHie (RContext (HsRecFields (GhcPass p) arg)) where
toHie :: RContext (HsRecFields (GhcPass p) arg) -> HieM [HieAST Type]
toHie (RC RecFieldContext
c (HsRecFields [LHsRecField (GhcPass p) arg]
fields Maybe (Located TypeIndex)
_)) = [RContext (LHsRecField (GhcPass p) arg)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RContext (LHsRecField (GhcPass p) arg)] -> HieM [HieAST Type])
-> [RContext (LHsRecField (GhcPass p) arg)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsRecField (GhcPass p) arg
-> RContext (LHsRecField (GhcPass p) arg))
-> [LHsRecField (GhcPass p) arg]
-> [RContext (LHsRecField (GhcPass p) arg)]
forall a b. (a -> b) -> [a] -> [b]
map (RecFieldContext
-> LHsRecField (GhcPass p) arg
-> RContext (LHsRecField (GhcPass p) arg)
forall a. RecFieldContext -> a -> RContext a
RC RecFieldContext
c) [LHsRecField (GhcPass p) arg]
fields
instance ( ToHie (RFContext (Located label))
, ToHie arg , HasLoc arg , Data arg
, Data label
) => ToHie (RContext (LHsRecField' label arg)) where
toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type]
toHie (RC RecFieldContext
c (L SrcSpan
span HsRecField' label arg
recfld)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsRecField' label arg -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsRecField' label arg
recfld SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsRecField' label arg
recfld of
HsRecField Located label
label arg
expr Bool
_ ->
[ RFContext (Located label) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RFContext (Located label) -> HieM [HieAST Type])
-> RFContext (Located label) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RecFieldContext
-> Maybe Span -> Located label -> RFContext (Located label)
forall a. RecFieldContext -> Maybe Span -> a -> RFContext a
RFC RecFieldContext
c (SrcSpan -> Maybe Span
getRealSpan (SrcSpan -> Maybe Span) -> SrcSpan -> Maybe Span
forall a b. (a -> b) -> a -> b
$ arg -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc arg
expr) Located label
label
, arg -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie arg
expr
]
instance ToHie (RFContext (LFieldOcc GhcRn)) where
toHie :: RFContext (Located (FieldOcc GhcRn)) -> HieM [HieAST Type]
toHie (RFC RecFieldContext
c Maybe Span
rhs (L SrcSpan
nspan FieldOcc GhcRn
f)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case FieldOcc GhcRn
f of
FieldOcc XCFieldOcc GhcRn
name Located RdrName
_ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
c Maybe Span
rhs) (SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L SrcSpan
nspan Name
XCFieldOcc GhcRn
name)
]
instance ToHie (RFContext (LFieldOcc GhcTc)) where
toHie :: RFContext (Located (FieldOcc GhcTc)) -> HieM [HieAST Type]
toHie (RFC RecFieldContext
c Maybe Span
rhs (L SrcSpan
nspan FieldOcc GhcTc
f)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case FieldOcc GhcTc
f of
FieldOcc XCFieldOcc GhcTc
var Located RdrName
_ ->
[ Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
c Maybe Span
rhs) (SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
nspan Id
XCFieldOcc GhcTc
var)
]
instance ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) where
toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]
toHie (RFC RecFieldContext
c Maybe Span
rhs (L SrcSpan
nspan AmbiguousFieldOcc GhcRn
afo)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case AmbiguousFieldOcc GhcRn
afo of
Unambiguous XUnambiguous GhcRn
name Located RdrName
_ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
c Maybe Span
rhs) (Located Name -> Context (Located Name))
-> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L SrcSpan
nspan Name
XUnambiguous GhcRn
name
]
Ambiguous XAmbiguous GhcRn
_name Located RdrName
_ ->
[ ]
instance ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) where
toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]
toHie (RFC RecFieldContext
c Maybe Span
rhs (L SrcSpan
nspan AmbiguousFieldOcc GhcTc
afo)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case AmbiguousFieldOcc GhcTc
afo of
Unambiguous XUnambiguous GhcTc
var Located RdrName
_ ->
[ Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
c Maybe Span
rhs) (SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
nspan Id
XUnambiguous GhcTc
var)
]
Ambiguous XAmbiguous GhcTc
var Located RdrName
_ ->
[ Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (GenLocated SrcSpan Id) -> HieM [HieAST Type])
-> Context (GenLocated SrcSpan Id) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo
-> GenLocated SrcSpan Id -> Context (GenLocated SrcSpan Id)
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
c Maybe Span
rhs) (SrcSpan -> Id -> GenLocated SrcSpan Id
forall l e. l -> e -> GenLocated l e
L SrcSpan
nspan Id
XAmbiguous GhcTc
var)
]
instance HiePass p => ToHie (RScoped (ApplicativeArg (GhcPass p))) where
toHie :: RScoped (ApplicativeArg (GhcPass p)) -> HieM [HieAST Type]
toHie (RS Scope
sc (ApplicativeArgOne XApplicativeArgOne (GhcPass p)
_ LPat (GhcPass p)
pat LHsExpr (GhcPass p)
expr Bool
_)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
forall a. Maybe a
Nothing Scope
sc Scope
NoScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
toHie (RS Scope
sc (ApplicativeArgMany XApplicativeArgMany (GhcPass p)
_ [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts HsExpr (GhcPass p)
_ LPat (GhcPass p)
pat HsStmtContext GhcRn
_)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
NoScope [Located (StmtLR (GhcPass p) (GhcPass p) (LHsExpr (GhcPass p)))]
stmts
, PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type])
-> PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Maybe Span
-> Scope
-> Scope
-> Located (Pat (GhcPass p))
-> PScoped (Located (Pat (GhcPass p)))
forall a. Maybe Span -> Scope -> Scope -> a -> PScoped a
PS Maybe Span
forall a. Maybe a
Nothing Scope
sc Scope
NoScope Located (Pat (GhcPass p))
LPat (GhcPass p)
pat
]
instance (ToHie arg, ToHie rec) => ToHie (HsConDetails arg rec) where
toHie :: HsConDetails arg rec -> HieM [HieAST Type]
toHie (PrefixCon [arg]
args) = [arg] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [arg]
args
toHie (RecCon rec
rec) = rec -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie rec
rec
toHie (InfixCon arg
a arg
b) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM [ arg -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie arg
a, arg -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie arg
b]
instance HiePass p => ToHie (LHsCmdTop (GhcPass p)) where
toHie :: LHsCmdTop (GhcPass p) -> HieM [HieAST Type]
toHie (L SrcSpan
span HsCmdTop (GhcPass p)
top) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsCmdTop (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsCmdTop (GhcPass p)
top SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsCmdTop (GhcPass p)
top of
HsCmdTop XCmdTop (GhcPass p)
_ LHsCmd (GhcPass p)
cmd ->
[ LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
cmd
]
instance HiePass p => ToHie (LHsCmd (GhcPass p)) where
toHie :: LHsCmd (GhcPass p) -> HieM [HieAST Type]
toHie (L SrcSpan
span HsCmd (GhcPass p)
cmd) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsCmd (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsCmd (GhcPass p)
cmd SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsCmd (GhcPass p)
cmd of
HsCmdArrApp XCmdArrApp (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsExpr (GhcPass p)
b HsArrAppType
_ Bool
_ ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
]
HsCmdArrForm XCmdArrForm (GhcPass p)
_ LHsExpr (GhcPass p)
a LexicalFixity
_ Maybe Fixity
_ [LHsCmdTop (GhcPass p)]
cmdtops ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, [LHsCmdTop (GhcPass p)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LHsCmdTop (GhcPass p)]
cmdtops
]
HsCmdApp XCmdApp (GhcPass p)
_ LHsCmd (GhcPass p)
a LHsExpr (GhcPass p)
b ->
[ LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
a
, LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
b
]
HsCmdLam XCmdLam (GhcPass p)
_ MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
mg ->
[ MatchGroup (GhcPass p) (LHsCmd (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
mg
]
HsCmdPar XCmdPar (GhcPass p)
_ LHsCmd (GhcPass p)
a ->
[ LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
a
]
HsCmdCase XCmdCase (GhcPass p)
_ LHsExpr (GhcPass p)
expr MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
alts ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
, MatchGroup (GhcPass p) (LHsCmd (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
alts
]
HsCmdLamCase XCmdLamCase (GhcPass p)
_ MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
alts ->
[ MatchGroup (GhcPass p) (LHsCmd (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie MatchGroup (GhcPass p) (LHsCmd (GhcPass p))
alts
]
HsCmdIf XCmdIf (GhcPass p)
_ SyntaxExpr (GhcPass p)
_ LHsExpr (GhcPass p)
a LHsCmd (GhcPass p)
b LHsCmd (GhcPass p)
c ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
a
, LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
b
, LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
c
]
HsCmdLet XCmdLet (GhcPass p)
_ LHsLocalBinds (GhcPass p)
binds LHsCmd (GhcPass p)
cmd' ->
[ RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type])
-> RScoped (LHsLocalBinds (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> LHsLocalBinds (GhcPass p) -> RScoped (LHsLocalBinds (GhcPass p))
forall a. Scope -> a -> RScoped a
RS (LHsCmd (GhcPass p) -> Scope
forall a. Located a -> Scope
mkLScope LHsCmd (GhcPass p)
cmd') LHsLocalBinds (GhcPass p)
binds
, LHsCmd (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsCmd (GhcPass p)
cmd'
]
HsCmdDo XCmdDo (GhcPass p)
_ (L SrcSpan
ispan [Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p)))]
stmts) ->
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
ispan
, [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p))))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p))))]
-> HieM [HieAST Type])
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p))))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope
-> [Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p)))]
-> [RScoped
(Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p))))]
forall a. Scope -> [Located a] -> [RScoped (Located a)]
listScopes Scope
NoScope [Located (StmtLR (GhcPass p) (GhcPass p) (LHsCmd (GhcPass p)))]
stmts
]
XCmd XXCmd (GhcPass p)
_ -> []
instance ToHie (TyClGroup GhcRn) where
toHie :: TyClGroup GhcRn -> HieM [HieAST Type]
toHie TyClGroup{ group_tyclds :: forall pass. TyClGroup pass -> [LTyClDecl pass]
group_tyclds = [LTyClDecl GhcRn]
classes
, group_roles :: forall pass. TyClGroup pass -> [LRoleAnnotDecl pass]
group_roles = [LRoleAnnotDecl GhcRn]
roles
, group_kisigs :: forall pass. TyClGroup pass -> [LStandaloneKindSig pass]
group_kisigs = [LStandaloneKindSig GhcRn]
sigs
, group_instds :: forall pass. TyClGroup pass -> [LInstDecl pass]
group_instds = [LInstDecl GhcRn]
instances } =
[HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ [LTyClDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LTyClDecl GhcRn]
classes
, [LStandaloneKindSig GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LStandaloneKindSig GhcRn]
sigs
, [LRoleAnnotDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LRoleAnnotDecl GhcRn]
roles
, [LInstDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LInstDecl GhcRn]
instances
]
instance ToHie (LTyClDecl GhcRn) where
toHie :: LTyClDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span TyClDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyClDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode TyClDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case TyClDecl GhcRn
decl of
FamDecl {tcdFam :: forall pass. TyClDecl pass -> FamilyDecl pass
tcdFam = FamilyDecl GhcRn
fdecl} ->
[ GenLocated SrcSpan (FamilyDecl GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (SrcSpan
-> FamilyDecl GhcRn -> GenLocated SrcSpan (FamilyDecl GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpan
span FamilyDecl GhcRn
fdecl)
]
SynDecl {tcdLName :: forall pass. TyClDecl pass -> Located (IdP pass)
tcdLName = Located (IdP GhcRn)
name, tcdTyVars :: forall pass. TyClDecl pass -> LHsQTyVars pass
tcdTyVars = LHsQTyVars GhcRn
vars, tcdRhs :: forall pass. TyClDecl pass -> LHsType pass
tcdRhs = GenLocated SrcSpan (HsType GhcRn)
typ} ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
SynDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type])
-> TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> LHsQTyVars GhcRn -> TScoped (LHsQTyVars GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan (HsType GhcRn) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc GenLocated SrcSpan (HsType GhcRn)
typ]) LHsQTyVars GhcRn
vars
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
typ
]
DataDecl {tcdLName :: forall pass. TyClDecl pass -> Located (IdP pass)
tcdLName = Located (IdP GhcRn)
name, tcdTyVars :: forall pass. TyClDecl pass -> LHsQTyVars pass
tcdTyVars = LHsQTyVars GhcRn
vars, tcdDataDefn :: forall pass. TyClDecl pass -> HsDataDefn pass
tcdDataDefn = HsDataDefn GhcRn
defn} ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
DataDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type])
-> TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> LHsQTyVars GhcRn -> TScoped (LHsQTyVars GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [Scope
quant_scope, Scope
rhs_scope]) LHsQTyVars GhcRn
vars
, HsDataDefn GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsDataDefn GhcRn
defn
]
where
quant_scope :: Scope
quant_scope = LHsContext GhcRn -> Scope
forall a. Located a -> Scope
mkLScope (LHsContext GhcRn -> Scope) -> LHsContext GhcRn -> Scope
forall a b. (a -> b) -> a -> b
$ HsDataDefn GhcRn -> LHsContext GhcRn
forall pass. HsDataDefn pass -> LHsContext pass
dd_ctxt HsDataDefn GhcRn
defn
rhs_scope :: Scope
rhs_scope = Scope
sig_sc Scope -> Scope -> Scope
`combineScopes` Scope
con_sc Scope -> Scope -> Scope
`combineScopes` Scope
deriv_sc
sig_sc :: Scope
sig_sc = Scope
-> (GenLocated SrcSpan (HsType GhcRn) -> Scope)
-> Maybe (GenLocated SrcSpan (HsType GhcRn))
-> Scope
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Scope
NoScope GenLocated SrcSpan (HsType GhcRn) -> Scope
forall a. Located a -> Scope
mkLScope (Maybe (GenLocated SrcSpan (HsType GhcRn)) -> Scope)
-> Maybe (GenLocated SrcSpan (HsType GhcRn)) -> Scope
forall a b. (a -> b) -> a -> b
$ HsDataDefn GhcRn -> Maybe (GenLocated SrcSpan (HsType GhcRn))
forall pass. HsDataDefn pass -> Maybe (LHsKind pass)
dd_kindSig HsDataDefn GhcRn
defn
con_sc :: Scope
con_sc = (Scope -> Scope -> Scope) -> Scope -> [Scope] -> Scope
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Scope -> Scope -> Scope
combineScopes Scope
NoScope ([Scope] -> Scope) -> [Scope] -> Scope
forall a b. (a -> b) -> a -> b
$ (LConDecl GhcRn -> Scope) -> [LConDecl GhcRn] -> [Scope]
forall a b. (a -> b) -> [a] -> [b]
map LConDecl GhcRn -> Scope
forall a. Located a -> Scope
mkLScope ([LConDecl GhcRn] -> [Scope]) -> [LConDecl GhcRn] -> [Scope]
forall a b. (a -> b) -> a -> b
$ HsDataDefn GhcRn -> [LConDecl GhcRn]
forall pass. HsDataDefn pass -> [LConDecl pass]
dd_cons HsDataDefn GhcRn
defn
deriv_sc :: Scope
deriv_sc = Located [LHsDerivingClause GhcRn] -> Scope
forall a. Located a -> Scope
mkLScope (Located [LHsDerivingClause GhcRn] -> Scope)
-> Located [LHsDerivingClause GhcRn] -> Scope
forall a b. (a -> b) -> a -> b
$ HsDataDefn GhcRn -> Located [LHsDerivingClause GhcRn]
forall pass. HsDataDefn pass -> HsDeriving pass
dd_derivs HsDataDefn GhcRn
defn
ClassDecl { tcdCtxt :: forall pass. TyClDecl pass -> LHsContext pass
tcdCtxt = LHsContext GhcRn
context
, tcdLName :: forall pass. TyClDecl pass -> Located (IdP pass)
tcdLName = Located (IdP GhcRn)
name
, tcdTyVars :: forall pass. TyClDecl pass -> LHsQTyVars pass
tcdTyVars = LHsQTyVars GhcRn
vars
, tcdFDs :: forall pass. TyClDecl pass -> [LHsFunDep pass]
tcdFDs = [LHsFunDep GhcRn]
deps
, tcdSigs :: forall pass. TyClDecl pass -> [LSig pass]
tcdSigs = [LSig GhcRn]
sigs
, tcdMeths :: forall pass. TyClDecl pass -> LHsBinds pass
tcdMeths = LHsBinds GhcRn
meths
, tcdATs :: forall pass. TyClDecl pass -> [LFamilyDecl pass]
tcdATs = [GenLocated SrcSpan (FamilyDecl GhcRn)]
typs
, tcdATDefs :: forall pass. TyClDecl pass -> [LTyFamDefltDecl pass]
tcdATDefs = [LTyFamDefltDecl GhcRn]
deftyps
} ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
ClassDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, LHsContext GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsContext GhcRn
context
, TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type])
-> TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> LHsQTyVars GhcRn -> TScoped (LHsQTyVars GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [Scope
context_scope, Scope
rhs_scope]) LHsQTyVars GhcRn
vars
, [Located (FunDep (Located Name))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [Located (FunDep (Located Name))]
[LHsFunDep GhcRn]
deps
, [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([SigContext (LSig GhcRn)] -> HieM [HieAST Type])
-> [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LSig GhcRn -> SigContext (LSig GhcRn))
-> [LSig GhcRn] -> [SigContext (LSig GhcRn)]
forall a b. (a -> b) -> [a] -> [b]
map (SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn)
forall a. SigInfo -> a -> SigContext a
SC (SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn))
-> SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn)
forall a b. (a -> b) -> a -> b
$ SigType -> Maybe Span -> SigInfo
SI SigType
ClassSig (Maybe Span -> SigInfo) -> Maybe Span -> SigInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) [LSig GhcRn]
sigs
, Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type])
-> Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsBindLR GhcRn GhcRn -> BindContext (LHsBindLR GhcRn GhcRn))
-> LHsBinds GhcRn -> Bag (BindContext (LHsBindLR GhcRn GhcRn))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BindType
-> Scope
-> LHsBindLR GhcRn GhcRn
-> BindContext (LHsBindLR GhcRn GhcRn)
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
InstanceBind Scope
ModuleScope) LHsBinds GhcRn
meths
, [GenLocated SrcSpan (FamilyDecl GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (FamilyDecl GhcRn)]
typs
, (LTyFamDefltDecl GhcRn -> HieM [HieAST Type])
-> [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (LTyFamDefltDecl GhcRn -> SrcSpan)
-> LTyFamDefltDecl GhcRn
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LTyFamDefltDecl GhcRn -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) [LTyFamDefltDecl GhcRn]
deftyps
, [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LTyFamDefltDecl GhcRn]
deftyps
]
where
context_scope :: Scope
context_scope = LHsContext GhcRn -> Scope
forall a. Located a -> Scope
mkLScope LHsContext GhcRn
context
rhs_scope :: Scope
rhs_scope = (Scope -> Scope -> Scope) -> [Scope] -> Scope
forall a. (a -> a -> a) -> [a] -> a
foldl1' Scope -> Scope -> Scope
combineScopes ([Scope] -> Scope) -> [Scope] -> Scope
forall a b. (a -> b) -> a -> b
$ (SrcSpan -> Scope) -> [SrcSpan] -> [Scope]
forall a b. (a -> b) -> [a] -> [b]
map SrcSpan -> Scope
mkScope
[ [Located (FunDep (Located Name))] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [Located (FunDep (Located Name))]
[LHsFunDep GhcRn]
deps, [LSig GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LSig GhcRn]
sigs, [LHsBindLR GhcRn GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc (LHsBinds GhcRn -> [LHsBindLR GhcRn GhcRn]
forall a. Bag a -> [a]
bagToList LHsBinds GhcRn
meths), [GenLocated SrcSpan (FamilyDecl GhcRn)] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [GenLocated SrcSpan (FamilyDecl GhcRn)]
typs, [LTyFamDefltDecl GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LTyFamDefltDecl GhcRn]
deftyps]
instance ToHie (LFamilyDecl GhcRn) where
toHie :: GenLocated SrcSpan (FamilyDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span FamilyDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ FamilyDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode FamilyDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case FamilyDecl GhcRn
decl of
FamilyDecl XCFamilyDecl GhcRn
_ FamilyInfo GhcRn
info Located (IdP GhcRn)
name LHsQTyVars GhcRn
vars LexicalFixity
_ LFamilyResultSig GhcRn
sig Maybe (LInjectivityAnn GhcRn)
inj ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
FamDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type])
-> TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> LHsQTyVars GhcRn -> TScoped (LHsQTyVars GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [Scope
rhsSpan]) LHsQTyVars GhcRn
vars
, FamilyInfo GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie FamilyInfo GhcRn
info
, RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type])
-> RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Scope -> LFamilyResultSig GhcRn -> RScoped (LFamilyResultSig GhcRn)
forall a. Scope -> a -> RScoped a
RS Scope
injSpan LFamilyResultSig GhcRn
sig
, Maybe (LInjectivityAnn GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LInjectivityAnn GhcRn)
inj
]
where
rhsSpan :: Scope
rhsSpan = Scope
sigSpan Scope -> Scope -> Scope
`combineScopes` Scope
injSpan
sigSpan :: Scope
sigSpan = SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ LFamilyResultSig GhcRn -> SrcSpan
forall l e. GenLocated l e -> l
getLoc LFamilyResultSig GhcRn
sig
injSpan :: Scope
injSpan = Scope
-> (LInjectivityAnn GhcRn -> Scope)
-> Maybe (LInjectivityAnn GhcRn)
-> Scope
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Scope
NoScope (SrcSpan -> Scope
mkScope (SrcSpan -> Scope)
-> (LInjectivityAnn GhcRn -> SrcSpan)
-> LInjectivityAnn GhcRn
-> Scope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LInjectivityAnn GhcRn -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) Maybe (LInjectivityAnn GhcRn)
inj
instance ToHie (FamilyInfo GhcRn) where
toHie :: FamilyInfo GhcRn -> HieM [HieAST Type]
toHie (ClosedTypeFamily (Just [LTyFamInstEqn GhcRn]
eqns)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ (LTyFamInstEqn GhcRn -> HieM [HieAST Type])
-> [LTyFamInstEqn GhcRn] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (LTyFamInstEqn GhcRn -> SrcSpan)
-> LTyFamInstEqn GhcRn
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LTyFamInstEqn GhcRn -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) [LTyFamInstEqn GhcRn]
eqns
, [TScoped (TyFamInstEqn GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TScoped (TyFamInstEqn GhcRn)] -> HieM [HieAST Type])
-> [TScoped (TyFamInstEqn GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LTyFamInstEqn GhcRn -> TScoped (TyFamInstEqn GhcRn))
-> [LTyFamInstEqn GhcRn] -> [TScoped (TyFamInstEqn GhcRn)]
forall a b. (a -> b) -> [a] -> [b]
map LTyFamInstEqn GhcRn -> TScoped (TyFamInstEqn GhcRn)
forall {a}. GenLocated SrcSpan a -> TScoped a
go [LTyFamInstEqn GhcRn]
eqns
]
where
go :: GenLocated SrcSpan a -> TScoped a
go (L SrcSpan
l a
ib) = TyVarScope -> a -> TScoped a
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [SrcSpan -> Scope
mkScope SrcSpan
l]) a
ib
toHie FamilyInfo GhcRn
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (RScoped (LFamilyResultSig GhcRn)) where
toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type]
toHie (RS Scope
sc (L SrcSpan
span FamilyResultSig GhcRn
sig)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ FamilyResultSig GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode FamilyResultSig GhcRn
sig SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case FamilyResultSig GhcRn
sig of
NoSig XNoSig GhcRn
_ ->
[]
KindSig XCKindSig GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
k ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
k
]
TyVarSig XTyVarSig GhcRn
_ LHsTyVarBndr () GhcRn
bndr ->
[ TVScoped (LHsTyVarBndr () GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TVScoped (LHsTyVarBndr () GhcRn) -> HieM [HieAST Type])
-> TVScoped (LHsTyVarBndr () GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> LHsTyVarBndr () GhcRn
-> TVScoped (LHsTyVarBndr () GhcRn)
forall a. TyVarScope -> Scope -> a -> TVScoped a
TVS ([Scope] -> TyVarScope
ResolvedScopes [Scope
sc]) Scope
NoScope LHsTyVarBndr () GhcRn
bndr
]
instance ToHie (Located (FunDep (Located Name))) where
toHie :: Located (FunDep (Located Name)) -> HieM [HieAST Type]
toHie (L SrcSpan
span fd :: FunDep (Located Name)
fd@([Located Name]
lhs, [Located Name]
rhs)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ FunDep (Located Name) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode FunDep (Located Name)
fd SrcSpan
span
, [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
lhs
, [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
rhs
]
instance (ToHie rhs, HasLoc rhs)
=> ToHie (TScoped (FamEqn GhcRn rhs)) where
toHie :: TScoped (FamEqn GhcRn rhs) -> HieM [HieAST Type]
toHie (TS TyVarScope
_ FamEqn GhcRn rhs
f) = FamEqn GhcRn rhs -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie FamEqn GhcRn rhs
f
instance (ToHie rhs, HasLoc rhs)
=> ToHie (FamEqn GhcRn rhs) where
toHie :: FamEqn GhcRn rhs -> HieM [HieAST Type]
toHie fe :: FamEqn GhcRn rhs
fe@(FamEqn XCFamEqn GhcRn rhs
_ Located (IdP GhcRn)
var Maybe [LHsTyVarBndr () GhcRn]
tybndrs HsTyPats GhcRn
pats LexicalFixity
_ rhs
rhs) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
InstDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan (SrcSpan -> Maybe Span) -> SrcSpan -> Maybe Span
forall a b. (a -> b) -> a -> b
$ FamEqn GhcRn rhs -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc FamEqn GhcRn rhs
fe) Located Name
Located (IdP GhcRn)
var
, Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type])
-> Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ([LHsTyVarBndr () GhcRn] -> [TVScoped (LHsTyVarBndr () GhcRn)])
-> Maybe [LHsTyVarBndr () GhcRn]
-> Maybe [TVScoped (LHsTyVarBndr () GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TyVarScope
-> Scope
-> [LHsTyVarBndr () GhcRn]
-> [TVScoped (LHsTyVarBndr () GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes ([Scope] -> TyVarScope
ResolvedScopes []) Scope
scope) Maybe [LHsTyVarBndr () GhcRn]
tybndrs
, HsTyPats GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsTyPats GhcRn
pats
, rhs -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie rhs
rhs
]
where scope :: Scope
scope = Scope -> Scope -> Scope
combineScopes Scope
patsScope Scope
rhsScope
patsScope :: Scope
patsScope = SrcSpan -> Scope
mkScope (HsTyPats GhcRn -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc HsTyPats GhcRn
pats)
rhsScope :: Scope
rhsScope = SrcSpan -> Scope
mkScope (rhs -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc rhs
rhs)
instance ToHie (LInjectivityAnn GhcRn) where
toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span InjectivityAnn GhcRn
ann) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ InjectivityAnn GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode InjectivityAnn GhcRn
ann SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case InjectivityAnn GhcRn
ann of
InjectivityAnn Located (IdP GhcRn)
lhs [Located (IdP GhcRn)]
rhs ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (IdP GhcRn)
lhs
, [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
[Located (IdP GhcRn)]
rhs
]
instance ToHie (HsDataDefn GhcRn) where
toHie :: HsDataDefn GhcRn -> HieM [HieAST Type]
toHie (HsDataDefn XCHsDataDefn GhcRn
_ NewOrData
_ LHsContext GhcRn
ctx Maybe (Located CType)
_ Maybe (GenLocated SrcSpan (HsType GhcRn))
mkind [LConDecl GhcRn]
cons Located [LHsDerivingClause GhcRn]
derivs) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ LHsContext GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsContext GhcRn
ctx
, Maybe (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (GenLocated SrcSpan (HsType GhcRn))
mkind
, [LConDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LConDecl GhcRn]
cons
, Located [LHsDerivingClause GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located [LHsDerivingClause GhcRn]
derivs
]
instance ToHie (HsDeriving GhcRn) where
toHie :: Located [LHsDerivingClause GhcRn] -> HieM [HieAST Type]
toHie (L SrcSpan
span [LHsDerivingClause GhcRn]
clauses) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
span
, [LHsDerivingClause GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LHsDerivingClause GhcRn]
clauses
]
instance ToHie (LHsDerivingClause GhcRn) where
toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span HsDerivingClause GhcRn
cl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsDerivingClause GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsDerivingClause GhcRn
cl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsDerivingClause GhcRn
cl of
HsDerivingClause XCHsDerivingClause GhcRn
_ Maybe (LDerivStrategy GhcRn)
strat (L SrcSpan
ispan [HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))]
tys) ->
[ Maybe (LDerivStrategy GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LDerivStrategy GhcRn)
strat
, SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
ispan
, [TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))]
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))]
-> HieM [HieAST Type])
-> [TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))))
-> [HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))]
-> [TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))]
forall a b. (a -> b) -> [a] -> [b]
map (TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [])) [HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))]
tys
]
instance ToHie (Located (DerivStrategy GhcRn)) where
toHie :: LDerivStrategy GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span DerivStrategy GhcRn
strat) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ DerivStrategy GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode DerivStrategy GhcRn
strat SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case DerivStrategy GhcRn
strat of
DerivStrategy GhcRn
StockStrategy -> []
DerivStrategy GhcRn
AnyclassStrategy -> []
DerivStrategy GhcRn
NewtypeStrategy -> []
ViaStrategy XViaStrategy GhcRn
s -> [ TScoped (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type])
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) XViaStrategy GhcRn
HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
s ]
instance ToHie (Located OverlapMode) where
toHie :: Located OverlapMode -> HieM [HieAST Type]
toHie (L SrcSpan
span OverlapMode
_) = SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
span
instance ToHie a => ToHie (HsScaled GhcRn a) where
toHie :: HsScaled GhcRn a -> HieM [HieAST Type]
toHie (HsScaled HsArrow GhcRn
w a
t) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM [GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (HsArrow GhcRn -> GenLocated SrcSpan (HsType GhcRn)
arrowToHsType HsArrow GhcRn
w), a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie a
t]
instance ToHie (LConDecl GhcRn) where
toHie :: LConDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span ConDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ConDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode ConDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case ConDecl GhcRn
decl of
ConDeclGADT { con_names :: forall pass. ConDecl pass -> [Located (IdP pass)]
con_names = [Located (IdP GhcRn)]
names, con_qvars :: forall pass. ConDecl pass -> [LHsTyVarBndr Specificity pass]
con_qvars = [LHsTyVarBndr Specificity GhcRn]
exp_vars, con_g_ext :: forall pass. ConDecl pass -> XConDeclGADT pass
con_g_ext = XConDeclGADT GhcRn
imp_vars
, con_mb_cxt :: forall pass. ConDecl pass -> Maybe (LHsContext pass)
con_mb_cxt = Maybe (LHsContext GhcRn)
ctx, con_args :: forall pass. ConDecl pass -> HsConDeclDetails pass
con_args = HsConDeclDetails GhcRn
args, con_res_ty :: forall pass. ConDecl pass -> LHsType pass
con_res_ty = GenLocated SrcSpan (HsType GhcRn)
typ } ->
[ [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
ConDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span)) [Located Name]
[Located (IdP GhcRn)]
names
, [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ [ [Context Name] -> HieM [HieAST Type]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly [Context Name]
bindings
, [TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type])
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> [LHsTyVarBndr Specificity GhcRn]
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes TyVarScope
resScope Scope
NoScope [LHsTyVarBndr Specificity GhcRn]
exp_vars ]
, Maybe (LHsContext GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LHsContext GhcRn)
ctx
, HsConDeclDetails GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsConDeclDetails GhcRn
args
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
typ
]
where
rhsScope :: Scope
rhsScope = Scope -> Scope -> Scope
combineScopes Scope
argsScope Scope
tyScope
ctxScope :: Scope
ctxScope = Scope
-> (LHsContext GhcRn -> Scope) -> Maybe (LHsContext GhcRn) -> Scope
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Scope
NoScope LHsContext GhcRn -> Scope
forall a. Located a -> Scope
mkLScope Maybe (LHsContext GhcRn)
ctx
argsScope :: Scope
argsScope = HsConDeclDetails GhcRn -> Scope
forall p. HsConDeclDetails p -> Scope
condecl_scope HsConDeclDetails GhcRn
args
tyScope :: Scope
tyScope = GenLocated SrcSpan (HsType GhcRn) -> Scope
forall a. Located a -> Scope
mkLScope GenLocated SrcSpan (HsType GhcRn)
typ
resScope :: TyVarScope
resScope = [Scope] -> TyVarScope
ResolvedScopes [Scope
ctxScope, Scope
rhsScope]
bindings :: [Context Name]
bindings = (Name -> Context Name) -> [Name] -> [Context Name]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Name -> Context Name
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Name -> Context Name)
-> ContextInfo -> Name -> Context Name
forall a b. (a -> b) -> a -> b
$ Scope -> TyVarScope -> ContextInfo
TyVarBind (SrcSpan -> Scope
mkScope ([LHsTyVarBndr Specificity GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LHsTyVarBndr Specificity GhcRn]
exp_vars)) TyVarScope
resScope) [Name]
XConDeclGADT GhcRn
imp_vars
ConDeclH98 { con_name :: forall pass. ConDecl pass -> Located (IdP pass)
con_name = Located (IdP GhcRn)
name, con_ex_tvs :: forall pass. ConDecl pass -> [LHsTyVarBndr Specificity pass]
con_ex_tvs = [LHsTyVarBndr Specificity GhcRn]
qvars
, con_mb_cxt :: forall pass. ConDecl pass -> Maybe (LHsContext pass)
con_mb_cxt = Maybe (LHsContext GhcRn)
ctx, con_args :: forall pass. ConDecl pass -> HsConDeclDetails pass
con_args = HsConDeclDetails GhcRn
dets } ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (DeclType -> Maybe Span -> ContextInfo
Decl DeclType
ConDec (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, [TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type])
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> [LHsTyVarBndr Specificity GhcRn]
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes ([Scope] -> TyVarScope
ResolvedScopes []) Scope
rhsScope [LHsTyVarBndr Specificity GhcRn]
qvars
, Maybe (LHsContext GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LHsContext GhcRn)
ctx
, HsConDeclDetails GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie HsConDeclDetails GhcRn
dets
]
where
rhsScope :: Scope
rhsScope = Scope -> Scope -> Scope
combineScopes Scope
ctxScope Scope
argsScope
ctxScope :: Scope
ctxScope = Scope
-> (LHsContext GhcRn -> Scope) -> Maybe (LHsContext GhcRn) -> Scope
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Scope
NoScope LHsContext GhcRn -> Scope
forall a. Located a -> Scope
mkLScope Maybe (LHsContext GhcRn)
ctx
argsScope :: Scope
argsScope = HsConDeclDetails GhcRn -> Scope
forall p. HsConDeclDetails p -> Scope
condecl_scope HsConDeclDetails GhcRn
dets
where condecl_scope :: HsConDeclDetails p -> Scope
condecl_scope :: forall p. HsConDeclDetails p -> Scope
condecl_scope HsConDeclDetails p
args = case HsConDeclDetails p
args of
PrefixCon [HsScaled p (LBangType p)]
xs -> (Scope -> Scope -> Scope) -> Scope -> [Scope] -> Scope
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Scope -> Scope -> Scope
combineScopes Scope
NoScope ([Scope] -> Scope) -> [Scope] -> Scope
forall a b. (a -> b) -> a -> b
$ (HsScaled p (LBangType p) -> Scope)
-> [HsScaled p (LBangType p)] -> [Scope]
forall a b. (a -> b) -> [a] -> [b]
map (LBangType p -> Scope
forall a. Located a -> Scope
mkLScope (LBangType p -> Scope)
-> (HsScaled p (LBangType p) -> LBangType p)
-> HsScaled p (LBangType p)
-> Scope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsScaled p (LBangType p) -> LBangType p
forall pass a. HsScaled pass a -> a
hsScaledThing) [HsScaled p (LBangType p)]
xs
InfixCon HsScaled p (LBangType p)
a HsScaled p (LBangType p)
b -> Scope -> Scope -> Scope
combineScopes (LBangType p -> Scope
forall a. Located a -> Scope
mkLScope (HsScaled p (LBangType p) -> LBangType p
forall pass a. HsScaled pass a -> a
hsScaledThing HsScaled p (LBangType p)
a))
(LBangType p -> Scope
forall a. Located a -> Scope
mkLScope (HsScaled p (LBangType p) -> LBangType p
forall pass a. HsScaled pass a -> a
hsScaledThing HsScaled p (LBangType p)
b))
RecCon Located [LConDeclField p]
x -> Located [LConDeclField p] -> Scope
forall a. Located a -> Scope
mkLScope Located [LConDeclField p]
x
instance ToHie (Located [LConDeclField GhcRn]) where
toHie :: GenLocated SrcSpan [LConDeclField GhcRn] -> HieM [HieAST Type]
toHie (L SrcSpan
span [LConDeclField GhcRn]
decls) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
span
, [LConDeclField GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LConDeclField GhcRn]
decls
]
instance ( HasLoc thing
, ToHie (TScoped thing)
) => ToHie (TScoped (HsImplicitBndrs GhcRn thing)) where
toHie :: TScoped (HsImplicitBndrs GhcRn thing) -> HieM [HieAST Type]
toHie (TS TyVarScope
sc (HsIB XHsIB GhcRn thing
ibrn thing
a)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ [Context Name] -> HieM [HieAST Type]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly ([Context Name] -> HieM [HieAST Type])
-> [Context Name] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Name -> Context Name) -> [Name] -> [Context Name]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Name -> Context Name
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Name -> Context Name)
-> ContextInfo -> Name -> Context Name
forall a b. (a -> b) -> a -> b
$ Scope -> TyVarScope -> ContextInfo
TyVarBind (SrcSpan -> Scope
mkScope SrcSpan
span) TyVarScope
sc) [Name]
XHsIB GhcRn thing
ibrn
, TScoped thing -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped thing -> HieM [HieAST Type])
-> TScoped thing -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> thing -> TScoped thing
forall a. TyVarScope -> a -> TScoped a
TS TyVarScope
sc thing
a
]
where span :: SrcSpan
span = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
instance ( HasLoc thing
, ToHie (TScoped thing)
) => ToHie (TScoped (HsWildCardBndrs GhcRn thing)) where
toHie :: TScoped (HsWildCardBndrs GhcRn thing) -> HieM [HieAST Type]
toHie (TS TyVarScope
sc (HsWC XHsWC GhcRn thing
names thing
a)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ [Context Name] -> HieM [HieAST Type]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly ([Context Name] -> HieM [HieAST Type])
-> [Context Name] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Name -> Context Name) -> [Name] -> [Context Name]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Name -> Context Name
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Name -> Context Name)
-> ContextInfo -> Name -> Context Name
forall a b. (a -> b) -> a -> b
$ Scope -> TyVarScope -> ContextInfo
TyVarBind (SrcSpan -> Scope
mkScope SrcSpan
span) TyVarScope
sc) [Name]
XHsWC GhcRn thing
names
, TScoped thing -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped thing -> HieM [HieAST Type])
-> TScoped thing -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> thing -> TScoped thing
forall a. TyVarScope -> a -> TScoped a
TS TyVarScope
sc thing
a
]
where span :: SrcSpan
span = thing -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc thing
a
instance ToHie (LStandaloneKindSig GhcRn) where
toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
sp StandaloneKindSig GhcRn
sig) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM [StandaloneKindSig GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode StandaloneKindSig GhcRn
sig SrcSpan
sp, StandaloneKindSig GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie StandaloneKindSig GhcRn
sig]
instance ToHie (StandaloneKindSig GhcRn) where
toHie :: StandaloneKindSig GhcRn -> HieM [HieAST Type]
toHie StandaloneKindSig GhcRn
sig = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ case StandaloneKindSig GhcRn
sig of
StandaloneKindSig XStandaloneKindSig GhcRn
_ Located (IdP GhcRn)
name HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
typ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
TyDecl Located Name
Located (IdP GhcRn)
name
, TScoped (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type])
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
typ
]
instance HiePass p => ToHie (SigContext (LSig (GhcPass p))) where
toHie :: SigContext (LSig (GhcPass p)) -> HieM [HieAST Type]
toHie (SC (SI SigType
styp Maybe Span
msp) (L SrcSpan
sp Sig (GhcPass p)
sig)) =
case forall (p :: Pass). HiePass p => HiePassEv p
hiePass @p of
HiePassEv p
HieTc -> [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
HiePassEv p
HieRn -> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Sig (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode Sig (GhcPass p)
sig SrcSpan
sp HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case Sig (GhcPass p)
sig of
TypeSig XTypeSig (GhcPass p)
_ [Located (IdP (GhcPass p))]
names LHsSigWcType (GhcPass p)
typ ->
[ [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
TyDecl) [Located Name]
[Located (IdP (GhcPass p))]
names
, TScoped (LHsSigWcType (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigWcType (GhcPass p)) -> HieM [HieAST Type])
-> TScoped (LHsSigWcType (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsSigWcType (GhcPass p) -> TScoped (LHsSigWcType (GhcPass p))
forall a. TyVarScope -> a -> TScoped a
TS ([Name] -> Maybe Span -> TyVarScope
UnresolvedScope ((Located Name -> Name) -> [Located Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Located Name -> Name
forall l e. GenLocated l e -> e
unLoc [Located Name]
[Located (IdP (GhcPass p))]
names) Maybe Span
forall a. Maybe a
Nothing) LHsSigWcType (GhcPass p)
typ
]
PatSynSig XPatSynSig (GhcPass p)
_ [Located (IdP (GhcPass p))]
names LHsSigType (GhcPass p)
typ ->
[ [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
TyDecl) [Located Name]
[Located (IdP (GhcPass p))]
names
, TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type])
-> TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsSigType (GhcPass p) -> TScoped (LHsSigType (GhcPass p))
forall a. TyVarScope -> a -> TScoped a
TS ([Name] -> Maybe Span -> TyVarScope
UnresolvedScope ((Located Name -> Name) -> [Located Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Located Name -> Name
forall l e. GenLocated l e -> e
unLoc [Located Name]
[Located (IdP (GhcPass p))]
names) Maybe Span
forall a. Maybe a
Nothing) LHsSigType (GhcPass p)
typ
]
ClassOpSig XClassOpSig (GhcPass p)
_ Bool
_ [Located (IdP (GhcPass p))]
names LHsSigType (GhcPass p)
typ ->
[ case SigType
styp of
SigType
ClassSig -> [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Located Name -> Context (Located Name))
-> ContextInfo -> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ Maybe Span -> ContextInfo
ClassTyDecl (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
sp) [Located Name]
[Located (IdP (GhcPass p))]
names
SigType
_ -> [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Located Name -> Context (Located Name))
-> ContextInfo -> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ ContextInfo
TyDecl) [Located Name]
[Located (IdP (GhcPass p))]
names
, TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type])
-> TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsSigType (GhcPass p) -> TScoped (LHsSigType (GhcPass p))
forall a. TyVarScope -> a -> TScoped a
TS ([Name] -> Maybe Span -> TyVarScope
UnresolvedScope ((Located Name -> Name) -> [Located Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Located Name -> Name
forall l e. GenLocated l e -> e
unLoc [Located Name]
[Located (IdP (GhcPass p))]
names) Maybe Span
msp) LHsSigType (GhcPass p)
typ
]
IdSig XIdSig (GhcPass p)
_ Id
_ -> []
FixSig XFixSig (GhcPass p)
_ FixitySig (GhcPass p)
fsig ->
[ GenLocated SrcSpan (FixitySig (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (FixitySig (GhcPass p)) -> HieM [HieAST Type])
-> GenLocated SrcSpan (FixitySig (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> FixitySig (GhcPass p)
-> GenLocated SrcSpan (FixitySig (GhcPass p))
forall l e. l -> e -> GenLocated l e
L SrcSpan
sp FixitySig (GhcPass p)
fsig
]
InlineSig XInlineSig (GhcPass p)
_ Located (IdP (GhcPass p))
name InlinePragma
_ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) Located Name
Located (IdP (GhcPass p))
name
]
SpecSig XSpecSig (GhcPass p)
_ Located (IdP (GhcPass p))
name [LHsSigType (GhcPass p)]
typs InlinePragma
_ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) Located Name
Located (IdP (GhcPass p))
name
, [TScoped (LHsSigType (GhcPass p))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TScoped (LHsSigType (GhcPass p))] -> HieM [HieAST Type])
-> [TScoped (LHsSigType (GhcPass p))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsSigType (GhcPass p) -> TScoped (LHsSigType (GhcPass p)))
-> [LHsSigType (GhcPass p)] -> [TScoped (LHsSigType (GhcPass p))]
forall a b. (a -> b) -> [a] -> [b]
map (TyVarScope
-> LHsSigType (GhcPass p) -> TScoped (LHsSigType (GhcPass p))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [])) [LHsSigType (GhcPass p)]
typs
]
SpecInstSig XSpecInstSig (GhcPass p)
_ SourceText
_ LHsSigType (GhcPass p)
typ ->
[ TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type])
-> TScoped (LHsSigType (GhcPass p)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> LHsSigType (GhcPass p) -> TScoped (LHsSigType (GhcPass p))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) LHsSigType (GhcPass p)
typ
]
MinimalSig XMinimalSig (GhcPass p)
_ SourceText
_ LBooleanFormula (Located (IdP (GhcPass p)))
form ->
[ LBooleanFormula (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LBooleanFormula (Located Name)
LBooleanFormula (Located (IdP (GhcPass p)))
form
]
SCCFunSig XSCCFunSig (GhcPass p)
_ SourceText
_ Located (IdP (GhcPass p))
name Maybe (Located StringLiteral)
mtxt ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) Located Name
Located (IdP (GhcPass p))
name
, HieM [HieAST Type]
-> (Located StringLiteral -> HieM [HieAST Type])
-> Maybe (Located StringLiteral)
-> HieM [HieAST Type]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (Located StringLiteral -> SrcSpan)
-> Located StringLiteral
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located StringLiteral -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) Maybe (Located StringLiteral)
mtxt
]
CompleteMatchSig XCompleteMatchSig (GhcPass p)
_ SourceText
_ (L SrcSpan
ispan [Located (IdP (GhcPass p))]
names) Maybe (Located (IdP (GhcPass p)))
typ ->
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
ispan
, [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
[Located (IdP (GhcPass p))]
names
, Maybe (Context (Located Name)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe (Context (Located Name)) -> HieM [HieAST Type])
-> Maybe (Context (Located Name)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> Maybe (Located Name) -> Maybe (Context (Located Name))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) Maybe (Located Name)
Maybe (Located (IdP (GhcPass p)))
typ
]
instance ToHie (LHsType GhcRn) where
toHie :: GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
x = TScoped (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type])
-> TScoped (GenLocated SrcSpan (HsType GhcRn))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> GenLocated SrcSpan (HsType GhcRn)
-> TScoped (GenLocated SrcSpan (HsType GhcRn))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) GenLocated SrcSpan (HsType GhcRn)
x
instance ToHie (TScoped (LHsType GhcRn)) where
toHie :: TScoped (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type]
toHie (TS TyVarScope
tsc (L SrcSpan
span HsType GhcRn
t)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsType GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsType GhcRn
t SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsType GhcRn
t of
HsForAllTy XForAllTy GhcRn
_ HsForAllTelescope GhcRn
tele GenLocated SrcSpan (HsType GhcRn)
body ->
let scope :: Scope
scope = SrcSpan -> Scope
mkScope (SrcSpan -> Scope) -> SrcSpan -> Scope
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan (HsType GhcRn) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc GenLocated SrcSpan (HsType GhcRn)
body in
[ case HsForAllTelescope GhcRn
tele of
HsForAllVis { hsf_vis_bndrs :: forall pass. HsForAllTelescope pass -> [LHsTyVarBndr () pass]
hsf_vis_bndrs = [LHsTyVarBndr () GhcRn]
bndrs } ->
[TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type])
-> [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> [LHsTyVarBndr () GhcRn]
-> [TVScoped (LHsTyVarBndr () GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes TyVarScope
tsc Scope
scope [LHsTyVarBndr () GhcRn]
bndrs
HsForAllInvis { hsf_invis_bndrs :: forall pass.
HsForAllTelescope pass -> [LHsTyVarBndr Specificity pass]
hsf_invis_bndrs = [LHsTyVarBndr Specificity GhcRn]
bndrs } ->
[TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TVScoped (LHsTyVarBndr Specificity GhcRn)] -> HieM [HieAST Type])
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> [LHsTyVarBndr Specificity GhcRn]
-> [TVScoped (LHsTyVarBndr Specificity GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes TyVarScope
tsc Scope
scope [LHsTyVarBndr Specificity GhcRn]
bndrs
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
body
]
HsQualTy XQualTy GhcRn
_ LHsContext GhcRn
ctx GenLocated SrcSpan (HsType GhcRn)
body ->
[ LHsContext GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsContext GhcRn
ctx
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
body
]
HsTyVar XTyVar GhcRn
_ PromotionFlag
_ Located (IdP GhcRn)
var ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (IdP GhcRn)
var
]
HsAppTy XAppTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a GenLocated SrcSpan (HsType GhcRn)
b ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
b
]
HsAppKindTy XAppKindTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
ty GenLocated SrcSpan (HsType GhcRn)
ki ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
ty
, TScoped (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (GenLocated SrcSpan (HsType GhcRn)) -> HieM [HieAST Type])
-> TScoped (GenLocated SrcSpan (HsType GhcRn))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> GenLocated SrcSpan (HsType GhcRn)
-> TScoped (GenLocated SrcSpan (HsType GhcRn))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) GenLocated SrcSpan (HsType GhcRn)
ki
]
HsFunTy XFunTy GhcRn
_ HsArrow GhcRn
w GenLocated SrcSpan (HsType GhcRn)
a GenLocated SrcSpan (HsType GhcRn)
b ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (HsArrow GhcRn -> GenLocated SrcSpan (HsType GhcRn)
arrowToHsType HsArrow GhcRn
w)
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
b
]
HsListTy XListTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
]
HsTupleTy XTupleTy GhcRn
_ HsTupleSort
_ [GenLocated SrcSpan (HsType GhcRn)]
tys ->
[ [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
tys
]
HsSumTy XSumTy GhcRn
_ [GenLocated SrcSpan (HsType GhcRn)]
tys ->
[ [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
tys
]
HsOpTy XOpTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a Located (IdP GhcRn)
op GenLocated SrcSpan (HsType GhcRn)
b ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
, Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (IdP GhcRn)
op
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
b
]
HsParTy XParTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
]
HsIParamTy XIParamTy GhcRn
_ Located HsIPName
ip GenLocated SrcSpan (HsType GhcRn)
ty ->
[ Located HsIPName -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located HsIPName
ip
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
ty
]
HsKindSig XKindSig GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a GenLocated SrcSpan (HsType GhcRn)
b ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
b
]
HsSpliceTy XSpliceTy GhcRn
_ HsSplice GhcRn
a ->
[ GenLocated SrcSpan (HsSplice GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (HsSplice GhcRn) -> HieM [HieAST Type])
-> GenLocated SrcSpan (HsSplice GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsSplice GhcRn -> GenLocated SrcSpan (HsSplice GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpan
span HsSplice GhcRn
a
]
HsDocTy XDocTy GhcRn
_ GenLocated SrcSpan (HsType GhcRn)
a LHsDocString
_ ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
a
]
HsBangTy XBangTy GhcRn
_ HsSrcBang
_ GenLocated SrcSpan (HsType GhcRn)
ty ->
[ GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
ty
]
HsRecTy XRecTy GhcRn
_ [LConDeclField GhcRn]
fields ->
[ [LConDeclField GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LConDeclField GhcRn]
fields
]
HsExplicitListTy XExplicitListTy GhcRn
_ PromotionFlag
_ [GenLocated SrcSpan (HsType GhcRn)]
tys ->
[ [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
tys
]
HsExplicitTupleTy XExplicitTupleTy GhcRn
_ [GenLocated SrcSpan (HsType GhcRn)]
tys ->
[ [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
tys
]
HsTyLit XTyLit GhcRn
_ HsTyLit
_ -> []
HsWildCardTy XWildCardTy GhcRn
_ -> []
HsStarTy XStarTy GhcRn
_ Bool
_ -> []
XHsType XXType GhcRn
_ -> []
instance (ToHie tm, ToHie ty) => ToHie (HsArg tm ty) where
toHie :: HsArg tm ty -> HieM [HieAST Type]
toHie (HsValArg tm
tm) = tm -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie tm
tm
toHie (HsTypeArg SrcSpan
_ ty
ty) = ty -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ty
ty
toHie (HsArgPar SrcSpan
sp) = SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
sp
instance Data flag => ToHie (TVScoped (LHsTyVarBndr flag GhcRn)) where
toHie :: TVScoped (LHsTyVarBndr flag GhcRn) -> HieM [HieAST Type]
toHie (TVS TyVarScope
tsc Scope
sc (L SrcSpan
span HsTyVarBndr flag GhcRn
bndr)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsTyVarBndr flag GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsTyVarBndr flag GhcRn
bndr SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsTyVarBndr flag GhcRn
bndr of
UserTyVar XUserTyVar GhcRn
_ flag
_ Located (IdP GhcRn)
var ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (Scope -> TyVarScope -> ContextInfo
TyVarBind Scope
sc TyVarScope
tsc) Located Name
Located (IdP GhcRn)
var
]
KindedTyVar XKindedTyVar GhcRn
_ flag
_ Located (IdP GhcRn)
var GenLocated SrcSpan (HsType GhcRn)
kind ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (Scope -> TyVarScope -> ContextInfo
TyVarBind Scope
sc TyVarScope
tsc) Located Name
Located (IdP GhcRn)
var
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
kind
]
instance ToHie (TScoped (LHsQTyVars GhcRn)) where
toHie :: TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type]
toHie (TS TyVarScope
sc (HsQTvs XHsQTvs GhcRn
implicits [LHsTyVarBndr () GhcRn]
vars)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ [Context Name] -> HieM [HieAST Type]
forall a. [Context Name] -> HieM [HieAST a]
bindingsOnly [Context Name]
bindings
, [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type])
-> [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> Scope
-> [LHsTyVarBndr () GhcRn]
-> [TVScoped (LHsTyVarBndr () GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes TyVarScope
sc Scope
NoScope [LHsTyVarBndr () GhcRn]
vars
]
where
varLoc :: SrcSpan
varLoc = [LHsTyVarBndr () GhcRn] -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc [LHsTyVarBndr () GhcRn]
vars
bindings :: [Context Name]
bindings = (Name -> Context Name) -> [Name] -> [Context Name]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Name -> Context Name
forall a. ContextInfo -> a -> Context a
C (ContextInfo -> Name -> Context Name)
-> ContextInfo -> Name -> Context Name
forall a b. (a -> b) -> a -> b
$ Scope -> TyVarScope -> ContextInfo
TyVarBind (SrcSpan -> Scope
mkScope SrcSpan
varLoc) TyVarScope
sc) [Name]
XHsQTvs GhcRn
implicits
instance ToHie (LHsContext GhcRn) where
toHie :: LHsContext GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span [GenLocated SrcSpan (HsType GhcRn)]
tys) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
span
, [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
tys
]
instance ToHie (LConDeclField GhcRn) where
toHie :: LConDeclField GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span ConDeclField GhcRn
field) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ConDeclField GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode ConDeclField GhcRn
field SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case ConDeclField GhcRn
field of
ConDeclField XConDeclField GhcRn
_ [Located (FieldOcc GhcRn)]
fields GenLocated SrcSpan (HsType GhcRn)
typ Maybe LHsDocString
_ ->
[ [RFContext (Located (FieldOcc GhcRn))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RFContext (Located (FieldOcc GhcRn))] -> HieM [HieAST Type])
-> [RFContext (Located (FieldOcc GhcRn))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located (FieldOcc GhcRn) -> RFContext (Located (FieldOcc GhcRn)))
-> [Located (FieldOcc GhcRn)]
-> [RFContext (Located (FieldOcc GhcRn))]
forall a b. (a -> b) -> [a] -> [b]
map (RecFieldContext
-> Maybe Span
-> Located (FieldOcc GhcRn)
-> RFContext (Located (FieldOcc GhcRn))
forall a. RecFieldContext -> Maybe Span -> a -> RFContext a
RFC RecFieldContext
RecFieldDecl (SrcSpan -> Maybe Span
getRealSpan (SrcSpan -> Maybe Span) -> SrcSpan -> Maybe Span
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan (HsType GhcRn) -> SrcSpan
forall a. HasLoc a => a -> SrcSpan
loc GenLocated SrcSpan (HsType GhcRn)
typ)) [Located (FieldOcc GhcRn)]
fields
, GenLocated SrcSpan (HsType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsType GhcRn)
typ
]
instance ToHie (LHsExpr a) => ToHie (ArithSeqInfo a) where
toHie :: ArithSeqInfo a -> HieM [HieAST Type]
toHie (From LHsExpr a
expr) = LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
expr
toHie (FromThen LHsExpr a
a LHsExpr a
b) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
a
, LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
b
]
toHie (FromTo LHsExpr a
a LHsExpr a
b) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
a
, LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
b
]
toHie (FromThenTo LHsExpr a
a LHsExpr a
b LHsExpr a
c) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
a
, LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
b
, LHsExpr a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr a
c
]
instance ToHie (LSpliceDecl GhcRn) where
toHie :: GenLocated SrcSpan (SpliceDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span SpliceDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SpliceDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode SpliceDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case SpliceDecl GhcRn
decl of
SpliceDecl XSpliceDecl GhcRn
_ GenLocated SrcSpan (HsSplice GhcRn)
splice SpliceExplicitFlag
_ ->
[ GenLocated SrcSpan (HsSplice GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie GenLocated SrcSpan (HsSplice GhcRn)
splice
]
instance ToHie (HsBracket a) where
toHie :: HsBracket a -> HieM [HieAST Type]
toHie HsBracket a
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie PendingRnSplice where
toHie :: PendingRnSplice -> HieM [HieAST Type]
toHie PendingRnSplice
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie PendingTcSplice where
toHie :: PendingTcSplice -> HieM [HieAST Type]
toHie PendingTcSplice
_ = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (LBooleanFormula (Located Name)) where
toHie :: LBooleanFormula (Located Name) -> HieM [HieAST Type]
toHie (L SrcSpan
span BooleanFormula (Located Name)
form) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ BooleanFormula (Located Name) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode BooleanFormula (Located Name)
form SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case BooleanFormula (Located Name)
form of
Var Located Name
a ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
a
]
And [LBooleanFormula (Located Name)]
forms ->
[ [LBooleanFormula (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LBooleanFormula (Located Name)]
forms
]
Or [LBooleanFormula (Located Name)]
forms ->
[ [LBooleanFormula (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LBooleanFormula (Located Name)]
forms
]
Parens LBooleanFormula (Located Name)
f ->
[ LBooleanFormula (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LBooleanFormula (Located Name)
f
]
instance ToHie (Located HsIPName) where
toHie :: Located HsIPName -> HieM [HieAST Type]
toHie (L SrcSpan
span HsIPName
e) = HsIPName -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsIPName
e SrcSpan
span
instance HiePass p => ToHie (Located (HsSplice (GhcPass p))) where
toHie :: Located (HsSplice (GhcPass p)) -> HieM [HieAST Type]
toHie (L SrcSpan
span HsSplice (GhcPass p)
sp) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ HsSplice (GhcPass p) -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode HsSplice (GhcPass p)
sp SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case HsSplice (GhcPass p)
sp of
HsTypedSplice XTypedSplice (GhcPass p)
_ SpliceDecoration
_ IdP (GhcPass p)
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsUntypedSplice XUntypedSplice (GhcPass p)
_ SpliceDecoration
_ IdP (GhcPass p)
_ LHsExpr (GhcPass p)
expr ->
[ LHsExpr (GhcPass p) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie LHsExpr (GhcPass p)
expr
]
HsQuasiQuote XQuasiQuote (GhcPass p)
_ IdP (GhcPass p)
_ IdP (GhcPass p)
_ SrcSpan
ispan FastString
_ ->
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
ispan
]
HsSpliced XSpliced (GhcPass p)
_ ThModFinalizers
_ HsSplicedThing (GhcPass p)
_ ->
[]
XSplice XXSplice (GhcPass p)
x -> case forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p of
#if __GLASGOW_HASKELL__ < 811
GhcPs -> noExtCon x
GhcRn -> noExtCon x
#endif
GhcPass p
GhcTc -> case XXSplice (GhcPass p)
x of
HsSplicedT DelayedSplice
_ -> []
instance ToHie (LRoleAnnotDecl GhcRn) where
toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span RoleAnnotDecl GhcRn
annot) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RoleAnnotDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode RoleAnnotDecl GhcRn
annot SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case RoleAnnotDecl GhcRn
annot of
RoleAnnotDecl XCRoleAnnotDecl GhcRn
_ Located (IdP GhcRn)
var [Located (Maybe Role)]
roles ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (IdP GhcRn)
var
, (Located (Maybe Role) -> HieM [HieAST Type])
-> [Located (Maybe Role)] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (Located (Maybe Role) -> SrcSpan)
-> Located (Maybe Role)
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located (Maybe Role) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) [Located (Maybe Role)]
roles
]
instance ToHie (LInstDecl GhcRn) where
toHie :: LInstDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span InstDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ InstDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode InstDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case InstDecl GhcRn
decl of
ClsInstD XClsInstD GhcRn
_ ClsInstDecl GhcRn
d ->
[ GenLocated SrcSpan (ClsInstDecl GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (ClsInstDecl GhcRn) -> HieM [HieAST Type])
-> GenLocated SrcSpan (ClsInstDecl GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> ClsInstDecl GhcRn -> GenLocated SrcSpan (ClsInstDecl GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpan
span ClsInstDecl GhcRn
d
]
DataFamInstD XDataFamInstD GhcRn
_ DataFamInstDecl GhcRn
d ->
[ GenLocated SrcSpan (DataFamInstDecl GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (GenLocated SrcSpan (DataFamInstDecl GhcRn) -> HieM [HieAST Type])
-> GenLocated SrcSpan (DataFamInstDecl GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> DataFamInstDecl GhcRn
-> GenLocated SrcSpan (DataFamInstDecl GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpan
span DataFamInstDecl GhcRn
d
]
TyFamInstD XTyFamInstD GhcRn
_ TyFamInstDecl GhcRn
d ->
[ LTyFamDefltDecl GhcRn -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (LTyFamDefltDecl GhcRn -> HieM [HieAST Type])
-> LTyFamDefltDecl GhcRn -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ SrcSpan -> TyFamInstDecl GhcRn -> LTyFamDefltDecl GhcRn
forall l e. l -> e -> GenLocated l e
L SrcSpan
span TyFamInstDecl GhcRn
d
]
instance ToHie (LClsInstDecl GhcRn) where
toHie :: GenLocated SrcSpan (ClsInstDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span ClsInstDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ TScoped (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type])
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [SrcSpan -> Scope
mkScope SrcSpan
span]) (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))))
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
forall pass. ClsInstDecl pass -> LHsSigType pass
cid_poly_ty ClsInstDecl GhcRn
decl
, Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type])
-> Bag (BindContext (LHsBindLR GhcRn GhcRn)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LHsBindLR GhcRn GhcRn -> BindContext (LHsBindLR GhcRn GhcRn))
-> LHsBinds GhcRn -> Bag (BindContext (LHsBindLR GhcRn GhcRn))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BindType
-> Scope
-> LHsBindLR GhcRn GhcRn
-> BindContext (LHsBindLR GhcRn GhcRn)
forall a. BindType -> Scope -> a -> BindContext a
BC BindType
InstanceBind Scope
ModuleScope) (LHsBinds GhcRn -> Bag (BindContext (LHsBindLR GhcRn GhcRn)))
-> LHsBinds GhcRn -> Bag (BindContext (LHsBindLR GhcRn GhcRn))
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> LHsBinds GhcRn
forall pass. ClsInstDecl pass -> LHsBinds pass
cid_binds ClsInstDecl GhcRn
decl
, [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([SigContext (LSig GhcRn)] -> HieM [HieAST Type])
-> [SigContext (LSig GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LSig GhcRn -> SigContext (LSig GhcRn))
-> [LSig GhcRn] -> [SigContext (LSig GhcRn)]
forall a b. (a -> b) -> [a] -> [b]
map (SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn)
forall a. SigInfo -> a -> SigContext a
SC (SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn))
-> SigInfo -> LSig GhcRn -> SigContext (LSig GhcRn)
forall a b. (a -> b) -> a -> b
$ SigType -> Maybe Span -> SigInfo
SI SigType
InstSig (Maybe Span -> SigInfo) -> Maybe Span -> SigInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) ([LSig GhcRn] -> [SigContext (LSig GhcRn)])
-> [LSig GhcRn] -> [SigContext (LSig GhcRn)]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> [LSig GhcRn]
forall pass. ClsInstDecl pass -> [LSig pass]
cid_sigs ClsInstDecl GhcRn
decl
, (LTyFamDefltDecl GhcRn -> HieM [HieAST Type])
-> [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (LTyFamDefltDecl GhcRn -> SrcSpan)
-> LTyFamDefltDecl GhcRn
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LTyFamDefltDecl GhcRn -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) ([LTyFamDefltDecl GhcRn] -> HieM [HieAST Type])
-> [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> [LTyFamDefltDecl GhcRn]
forall pass. ClsInstDecl pass -> [LTyFamInstDecl pass]
cid_tyfam_insts ClsInstDecl GhcRn
decl
, [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([LTyFamDefltDecl GhcRn] -> HieM [HieAST Type])
-> [LTyFamDefltDecl GhcRn] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> [LTyFamDefltDecl GhcRn]
forall pass. ClsInstDecl pass -> [LTyFamInstDecl pass]
cid_tyfam_insts ClsInstDecl GhcRn
decl
, (GenLocated SrcSpan (DataFamInstDecl GhcRn) -> HieM [HieAST Type])
-> [GenLocated SrcSpan (DataFamInstDecl GhcRn)]
-> HieM [HieAST Type]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type])
-> (GenLocated SrcSpan (DataFamInstDecl GhcRn) -> SrcSpan)
-> GenLocated SrcSpan (DataFamInstDecl GhcRn)
-> HieM [HieAST Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpan (DataFamInstDecl GhcRn) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc) ([GenLocated SrcSpan (DataFamInstDecl GhcRn)]
-> HieM [HieAST Type])
-> [GenLocated SrcSpan (DataFamInstDecl GhcRn)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> [GenLocated SrcSpan (DataFamInstDecl GhcRn)]
forall pass. ClsInstDecl pass -> [LDataFamInstDecl pass]
cid_datafam_insts ClsInstDecl GhcRn
decl
, [GenLocated SrcSpan (DataFamInstDecl GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([GenLocated SrcSpan (DataFamInstDecl GhcRn)]
-> HieM [HieAST Type])
-> [GenLocated SrcSpan (DataFamInstDecl GhcRn)]
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> [GenLocated SrcSpan (DataFamInstDecl GhcRn)]
forall pass. ClsInstDecl pass -> [LDataFamInstDecl pass]
cid_datafam_insts ClsInstDecl GhcRn
decl
, Maybe (Located OverlapMode) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe (Located OverlapMode) -> HieM [HieAST Type])
-> Maybe (Located OverlapMode) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ClsInstDecl GhcRn -> Maybe (Located OverlapMode)
forall pass. ClsInstDecl pass -> Maybe (Located OverlapMode)
cid_overlap_mode ClsInstDecl GhcRn
decl
]
instance ToHie (LDataFamInstDecl GhcRn) where
toHie :: GenLocated SrcSpan (DataFamInstDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
sp (DataFamInstDecl FamInstEqn GhcRn (HsDataDefn GhcRn)
d)) = TScoped (FamInstEqn GhcRn (HsDataDefn GhcRn)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (FamInstEqn GhcRn (HsDataDefn GhcRn))
-> HieM [HieAST Type])
-> TScoped (FamInstEqn GhcRn (HsDataDefn GhcRn))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> FamInstEqn GhcRn (HsDataDefn GhcRn)
-> TScoped (FamInstEqn GhcRn (HsDataDefn GhcRn))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [SrcSpan -> Scope
mkScope SrcSpan
sp]) FamInstEqn GhcRn (HsDataDefn GhcRn)
d
instance ToHie (LTyFamInstDecl GhcRn) where
toHie :: LTyFamDefltDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
sp (TyFamInstDecl TyFamInstEqn GhcRn
d)) = TScoped (TyFamInstEqn GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (TyFamInstEqn GhcRn) -> HieM [HieAST Type])
-> TScoped (TyFamInstEqn GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> TyFamInstEqn GhcRn -> TScoped (TyFamInstEqn GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [SrcSpan -> Scope
mkScope SrcSpan
sp]) TyFamInstEqn GhcRn
d
instance ToHie (Context a)
=> ToHie (PatSynFieldContext (RecordPatSynField a)) where
toHie :: PatSynFieldContext (RecordPatSynField a) -> HieM [HieAST Type]
toHie (PSC Maybe Span
sp (RecordPatSynField a
a a
b)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ Context a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context a -> HieM [HieAST Type])
-> Context a -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> a -> Context a
forall a. ContextInfo -> a -> Context a
C (RecFieldContext -> Maybe Span -> ContextInfo
RecField RecFieldContext
RecFieldDecl Maybe Span
sp) a
a
, Context a -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context a -> HieM [HieAST Type])
-> Context a -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> a -> Context a
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use a
b
]
instance ToHie (LDerivDecl GhcRn) where
toHie :: GenLocated SrcSpan (DerivDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span DerivDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ DerivDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode DerivDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case DerivDecl GhcRn
decl of
DerivDecl XCDerivDecl GhcRn
_ LHsSigWcType GhcRn
typ Maybe (LDerivStrategy GhcRn)
strat Maybe (Located OverlapMode)
overlap ->
[ TScoped (LHsSigWcType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (LHsSigWcType GhcRn) -> HieM [HieAST Type])
-> TScoped (LHsSigWcType GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> LHsSigWcType GhcRn -> TScoped (LHsSigWcType GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) LHsSigWcType GhcRn
typ
, Maybe (LDerivStrategy GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (LDerivStrategy GhcRn)
strat
, Maybe (Located OverlapMode) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Maybe (Located OverlapMode)
overlap
]
instance ToHie (LFixitySig GhcRn) where
toHie :: GenLocated SrcSpan (FixitySig GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span FixitySig GhcRn
sig) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ FixitySig GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode FixitySig GhcRn
sig SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case FixitySig GhcRn
sig of
FixitySig XFixitySig GhcRn
_ [Located (IdP GhcRn)]
vars Fixity
_ ->
[ [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
[Located (IdP GhcRn)]
vars
]
instance ToHie (LDefaultDecl GhcRn) where
toHie :: GenLocated SrcSpan (DefaultDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span DefaultDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ DefaultDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode DefaultDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case DefaultDecl GhcRn
decl of
DefaultDecl XCDefaultDecl GhcRn
_ [GenLocated SrcSpan (HsType GhcRn)]
typs ->
[ [GenLocated SrcSpan (HsType GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [GenLocated SrcSpan (HsType GhcRn)]
typs
]
instance ToHie (LForeignDecl GhcRn) where
toHie :: GenLocated SrcSpan (ForeignDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span ForeignDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ForeignDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode ForeignDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case ForeignDecl GhcRn
decl of
ForeignImport {fd_name :: forall pass. ForeignDecl pass -> Located (IdP pass)
fd_name = Located (IdP GhcRn)
name, fd_sig_ty :: forall pass. ForeignDecl pass -> LHsSigType pass
fd_sig_ty = HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
sig, fd_fi :: forall pass. ForeignDecl pass -> ForeignImport
fd_fi = ForeignImport
fi} ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (BindType -> Scope -> Maybe Span -> ContextInfo
ValBind BindType
RegularBind Scope
ModuleScope (Maybe Span -> ContextInfo) -> Maybe Span -> ContextInfo
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Span
getRealSpan SrcSpan
span) Located Name
Located (IdP GhcRn)
name
, TScoped (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type])
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
sig
, ForeignImport -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ForeignImport
fi
]
ForeignExport {fd_name :: forall pass. ForeignDecl pass -> Located (IdP pass)
fd_name = Located (IdP GhcRn)
name, fd_sig_ty :: forall pass. ForeignDecl pass -> LHsSigType pass
fd_sig_ty = HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
sig, fd_fe :: forall pass. ForeignDecl pass -> ForeignExport
fd_fe = ForeignExport
fe} ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located Name
Located (IdP GhcRn)
name
, TScoped (HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type])
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
-> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope
-> HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
-> TScoped
(HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn)))
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes []) HsImplicitBndrs GhcRn (GenLocated SrcSpan (HsType GhcRn))
sig
, ForeignExport -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ForeignExport
fe
]
instance ToHie ForeignImport where
toHie :: ForeignImport -> HieM [HieAST Type]
toHie (CImport (L SrcSpan
a CCallConv
_) (L SrcSpan
b Safety
_) Maybe Header
_ CImportSpec
_ (L SrcSpan
c SourceText
_)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
a
, SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
b
, SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
c
]
instance ToHie ForeignExport where
toHie :: ForeignExport -> HieM [HieAST Type]
toHie (CExport (L SrcSpan
a CExportSpec
_) (L SrcSpan
b SourceText
_)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
a
, SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
b
]
instance ToHie (LWarnDecls GhcRn) where
toHie :: GenLocated SrcSpan (WarnDecls GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span WarnDecls GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ WarnDecls GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode WarnDecls GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case WarnDecls GhcRn
decl of
Warnings XWarnings GhcRn
_ SourceText
_ [LWarnDecl GhcRn]
warnings ->
[ [LWarnDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LWarnDecl GhcRn]
warnings
]
instance ToHie (LWarnDecl GhcRn) where
toHie :: LWarnDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span WarnDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ WarnDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode WarnDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case WarnDecl GhcRn
decl of
Warning XWarning GhcRn
_ [Located (IdP GhcRn)]
vars WarningTxt
_ ->
[ [Context (Located Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([Context (Located Name)] -> HieM [HieAST Type])
-> [Context (Located Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located Name -> Context (Located Name))
-> [Located Name] -> [Context (Located Name)]
forall a b. (a -> b) -> [a] -> [b]
map (ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use) [Located Name]
[Located (IdP GhcRn)]
vars
]
instance ToHie (LAnnDecl GhcRn) where
toHie :: GenLocated SrcSpan (AnnDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span AnnDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ AnnDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode AnnDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case AnnDecl GhcRn
decl of
HsAnnotation XHsAnnotation GhcRn
_ SourceText
_ AnnProvenance (IdP GhcRn)
prov Located (HsExpr GhcRn)
expr ->
[ AnnProvenance Name -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie AnnProvenance Name
AnnProvenance (IdP GhcRn)
prov
, Located (HsExpr GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located (HsExpr GhcRn)
expr
]
instance ToHie (Context (Located a)) => ToHie (AnnProvenance a) where
toHie :: AnnProvenance a -> HieM [HieAST Type]
toHie (ValueAnnProvenance Located a
a) = Context (Located a) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located a) -> HieM [HieAST Type])
-> Context (Located a) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located a -> Context (Located a)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located a
a
toHie (TypeAnnProvenance Located a
a) = Context (Located a) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located a) -> HieM [HieAST Type])
-> Context (Located a) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located a -> Context (Located a)
forall a. ContextInfo -> a -> Context a
C ContextInfo
Use Located a
a
toHie AnnProvenance a
ModuleAnnProvenance = [HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance ToHie (LRuleDecls GhcRn) where
toHie :: GenLocated SrcSpan (RuleDecls GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span RuleDecls GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RuleDecls GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode RuleDecls GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case RuleDecls GhcRn
decl of
HsRules XCRuleDecls GhcRn
_ SourceText
_ [LRuleDecl GhcRn]
rules ->
[ [LRuleDecl GhcRn] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie [LRuleDecl GhcRn]
rules
]
instance ToHie (LRuleDecl GhcRn) where
toHie :: LRuleDecl GhcRn -> HieM [HieAST Type]
toHie (L SrcSpan
span r :: RuleDecl GhcRn
r@(HsRule XHsRule GhcRn
_ Located (SourceText, FastString)
rname Activation
_ Maybe [LHsTyVarBndr () (NoGhcTc GhcRn)]
tybndrs [LRuleBndr GhcRn]
bndrs Located (HsExpr GhcRn)
exprA Located (HsExpr GhcRn)
exprB)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM
[ RuleDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode RuleDecl GhcRn
r SrcSpan
span
, SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly (SrcSpan -> HieM [HieAST Type]) -> SrcSpan -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ Located (SourceText, FastString) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located (SourceText, FastString)
rname
, Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type])
-> Maybe [TVScoped (LHsTyVarBndr () GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ([LHsTyVarBndr () GhcRn] -> [TVScoped (LHsTyVarBndr () GhcRn)])
-> Maybe [LHsTyVarBndr () GhcRn]
-> Maybe [TVScoped (LHsTyVarBndr () GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TyVarScope
-> Scope
-> [LHsTyVarBndr () GhcRn]
-> [TVScoped (LHsTyVarBndr () GhcRn)]
forall flag a.
TyVarScope
-> Scope
-> [LHsTyVarBndr flag a]
-> [TVScoped (LHsTyVarBndr flag a)]
tvScopes ([Scope] -> TyVarScope
ResolvedScopes []) Scope
scope) Maybe [LHsTyVarBndr () GhcRn]
Maybe [LHsTyVarBndr () (NoGhcTc GhcRn)]
tybndrs
, [RScoped (LRuleBndr GhcRn)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([RScoped (LRuleBndr GhcRn)] -> HieM [HieAST Type])
-> [RScoped (LRuleBndr GhcRn)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LRuleBndr GhcRn -> RScoped (LRuleBndr GhcRn))
-> [LRuleBndr GhcRn] -> [RScoped (LRuleBndr GhcRn)]
forall a b. (a -> b) -> [a] -> [b]
map (Scope -> LRuleBndr GhcRn -> RScoped (LRuleBndr GhcRn)
forall a. Scope -> a -> RScoped a
RS (Scope -> LRuleBndr GhcRn -> RScoped (LRuleBndr GhcRn))
-> Scope -> LRuleBndr GhcRn -> RScoped (LRuleBndr GhcRn)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Scope
mkScope SrcSpan
span) [LRuleBndr GhcRn]
bndrs
, Located (HsExpr GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located (HsExpr GhcRn)
exprA
, Located (HsExpr GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie Located (HsExpr GhcRn)
exprB
]
where scope :: Scope
scope = Scope
bndrs_sc Scope -> Scope -> Scope
`combineScopes` Scope
exprA_sc Scope -> Scope -> Scope
`combineScopes` Scope
exprB_sc
bndrs_sc :: Scope
bndrs_sc = Scope
-> (LRuleBndr GhcRn -> Scope) -> Maybe (LRuleBndr GhcRn) -> Scope
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Scope
NoScope LRuleBndr GhcRn -> Scope
forall a. Located a -> Scope
mkLScope ([LRuleBndr GhcRn] -> Maybe (LRuleBndr GhcRn)
forall a. [a] -> Maybe a
listToMaybe [LRuleBndr GhcRn]
bndrs)
exprA_sc :: Scope
exprA_sc = Located (HsExpr GhcRn) -> Scope
forall a. Located a -> Scope
mkLScope Located (HsExpr GhcRn)
exprA
exprB_sc :: Scope
exprB_sc = Located (HsExpr GhcRn) -> Scope
forall a. Located a -> Scope
mkLScope Located (HsExpr GhcRn)
exprB
instance ToHie (RScoped (LRuleBndr GhcRn)) where
toHie :: RScoped (LRuleBndr GhcRn) -> HieM [HieAST Type]
toHie (RS Scope
sc (L SrcSpan
span RuleBndr GhcRn
bndr)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ RuleBndr GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode RuleBndr GhcRn
bndr SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case RuleBndr GhcRn
bndr of
RuleBndr XCRuleBndr GhcRn
_ Located (IdP GhcRn)
var ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (BindType -> Scope -> Maybe Span -> ContextInfo
ValBind BindType
RegularBind Scope
sc Maybe Span
forall a. Maybe a
Nothing) Located Name
Located (IdP GhcRn)
var
]
RuleBndrSig XRuleBndrSig GhcRn
_ Located (IdP GhcRn)
var HsPatSigType GhcRn
typ ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (BindType -> Scope -> Maybe Span -> ContextInfo
ValBind BindType
RegularBind Scope
sc Maybe Span
forall a. Maybe a
Nothing) Located Name
Located (IdP GhcRn)
var
, TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type])
-> TScoped (HsPatSigType GhcRn) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ TyVarScope -> HsPatSigType GhcRn -> TScoped (HsPatSigType GhcRn)
forall a. TyVarScope -> a -> TScoped a
TS ([Scope] -> TyVarScope
ResolvedScopes [Scope
sc]) HsPatSigType GhcRn
typ
]
instance ToHie (LImportDecl GhcRn) where
toHie :: GenLocated SrcSpan (ImportDecl GhcRn) -> HieM [HieAST Type]
toHie (L SrcSpan
span ImportDecl GhcRn
decl) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ImportDecl GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode ImportDecl GhcRn
decl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case ImportDecl GhcRn
decl of
ImportDecl { ideclName :: forall pass. ImportDecl pass -> Located ModuleName
ideclName = Located ModuleName
name, ideclAs :: forall pass. ImportDecl pass -> Maybe (Located ModuleName)
ideclAs = Maybe (Located ModuleName)
as, ideclHiding :: forall pass. ImportDecl pass -> Maybe (Bool, Located [LIE pass])
ideclHiding = Maybe (Bool, Located [LIE GhcRn])
hidden } ->
[ IEContext (Located ModuleName) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (Located ModuleName) -> HieM [HieAST Type])
-> IEContext (Located ModuleName) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> Located ModuleName -> IEContext (Located ModuleName)
forall a. IEType -> a -> IEContext a
IEC IEType
Import Located ModuleName
name
, Maybe (IEContext (Located ModuleName)) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Maybe (IEContext (Located ModuleName)) -> HieM [HieAST Type])
-> Maybe (IEContext (Located ModuleName)) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located ModuleName -> IEContext (Located ModuleName))
-> Maybe (Located ModuleName)
-> Maybe (IEContext (Located ModuleName))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (IEType -> Located ModuleName -> IEContext (Located ModuleName)
forall a. IEType -> a -> IEContext a
IEC IEType
ImportAs) Maybe (Located ModuleName)
as
, HieM [HieAST Type]
-> ((Bool, Located [LIE GhcRn]) -> HieM [HieAST Type])
-> Maybe (Bool, Located [LIE GhcRn])
-> HieM [HieAST Type]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([HieAST Type] -> HieM [HieAST Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) (Bool, Located [LIE GhcRn]) -> HieM [HieAST Type]
forall {a}.
ToHie (IEContext a) =>
(Bool, GenLocated SrcSpan [a]) -> HieM [HieAST Type]
goIE Maybe (Bool, Located [LIE GhcRn])
hidden
]
where
goIE :: (Bool, GenLocated SrcSpan [a]) -> HieM [HieAST Type]
goIE (Bool
hiding, (L SrcSpan
sp [a]
liens)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$
[ SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a.
Monad m =>
SrcSpan -> ReaderT NodeOrigin m [HieAST a]
locOnly SrcSpan
sp
, [IEContext a] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([IEContext a] -> HieM [HieAST Type])
-> [IEContext a] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (a -> IEContext a) -> [a] -> [IEContext a]
forall a b. (a -> b) -> [a] -> [b]
map (IEType -> a -> IEContext a
forall a. IEType -> a -> IEContext a
IEC IEType
c) [a]
liens
]
where
c :: IEType
c = if Bool
hiding then IEType
ImportHiding else IEType
Import
instance ToHie (IEContext (LIE GhcRn)) where
toHie :: IEContext (LIE GhcRn) -> HieM [HieAST Type]
toHie (IEC IEType
c (L SrcSpan
span IE GhcRn
ie)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IE GhcRn -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode IE GhcRn
ie SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case IE GhcRn
ie of
IEVar XIEVar GhcRn
_ LIEWrappedName (IdP GhcRn)
n ->
[ IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (LIEWrappedName Name) -> HieM [HieAST Type])
-> IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> LIEWrappedName Name -> IEContext (LIEWrappedName Name)
forall a. IEType -> a -> IEContext a
IEC IEType
c LIEWrappedName Name
LIEWrappedName (IdP GhcRn)
n
]
IEThingAbs XIEThingAbs GhcRn
_ LIEWrappedName (IdP GhcRn)
n ->
[ IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (LIEWrappedName Name) -> HieM [HieAST Type])
-> IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> LIEWrappedName Name -> IEContext (LIEWrappedName Name)
forall a. IEType -> a -> IEContext a
IEC IEType
c LIEWrappedName Name
LIEWrappedName (IdP GhcRn)
n
]
IEThingAll XIEThingAll GhcRn
_ LIEWrappedName (IdP GhcRn)
n ->
[ IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (LIEWrappedName Name) -> HieM [HieAST Type])
-> IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> LIEWrappedName Name -> IEContext (LIEWrappedName Name)
forall a. IEType -> a -> IEContext a
IEC IEType
c LIEWrappedName Name
LIEWrappedName (IdP GhcRn)
n
]
IEThingWith XIEThingWith GhcRn
_ LIEWrappedName (IdP GhcRn)
n IEWildcard
_ [LIEWrappedName (IdP GhcRn)]
ns [Located (FieldLbl (IdP GhcRn))]
flds ->
[ IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (LIEWrappedName Name) -> HieM [HieAST Type])
-> IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> LIEWrappedName Name -> IEContext (LIEWrappedName Name)
forall a. IEType -> a -> IEContext a
IEC IEType
c LIEWrappedName Name
LIEWrappedName (IdP GhcRn)
n
, [IEContext (LIEWrappedName Name)] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([IEContext (LIEWrappedName Name)] -> HieM [HieAST Type])
-> [IEContext (LIEWrappedName Name)] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (LIEWrappedName Name -> IEContext (LIEWrappedName Name))
-> [LIEWrappedName Name] -> [IEContext (LIEWrappedName Name)]
forall a b. (a -> b) -> [a] -> [b]
map (IEType -> LIEWrappedName Name -> IEContext (LIEWrappedName Name)
forall a. IEType -> a -> IEContext a
IEC IEType
c) [LIEWrappedName Name]
[LIEWrappedName (IdP GhcRn)]
ns
, [IEContext (Located (FieldLbl Name))] -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie ([IEContext (Located (FieldLbl Name))] -> HieM [HieAST Type])
-> [IEContext (Located (FieldLbl Name))] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ (Located (FieldLbl Name) -> IEContext (Located (FieldLbl Name)))
-> [Located (FieldLbl Name)]
-> [IEContext (Located (FieldLbl Name))]
forall a b. (a -> b) -> [a] -> [b]
map (IEType
-> Located (FieldLbl Name) -> IEContext (Located (FieldLbl Name))
forall a. IEType -> a -> IEContext a
IEC IEType
c) [Located (FieldLbl Name)]
[Located (FieldLbl (IdP GhcRn))]
flds
]
IEModuleContents XIEModuleContents GhcRn
_ Located ModuleName
n ->
[ IEContext (Located ModuleName) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (IEContext (Located ModuleName) -> HieM [HieAST Type])
-> IEContext (Located ModuleName) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEType -> Located ModuleName -> IEContext (Located ModuleName)
forall a. IEType -> a -> IEContext a
IEC IEType
c Located ModuleName
n
]
IEGroup XIEGroup GhcRn
_ TypeIndex
_ HsDocString
_ -> []
IEDoc XIEDoc GhcRn
_ HsDocString
_ -> []
IEDocNamed XIEDocNamed GhcRn
_ FilePath
_ -> []
instance ToHie (IEContext (LIEWrappedName Name)) where
toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]
toHie (IEC IEType
c (L SrcSpan
span IEWrappedName Name
iewn)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ IEWrappedName Name -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode IEWrappedName Name
iewn SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case IEWrappedName Name
iewn of
IEName Located Name
n ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (IEType -> ContextInfo
IEThing IEType
c) Located Name
n
]
IEPattern Located Name
p ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (IEType -> ContextInfo
IEThing IEType
c) Located Name
p
]
IEType Located Name
n ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (IEType -> ContextInfo
IEThing IEType
c) Located Name
n
]
instance ToHie (IEContext (Located (FieldLbl Name))) where
toHie :: IEContext (Located (FieldLbl Name)) -> HieM [HieAST Type]
toHie (IEC IEType
c (L SrcSpan
span FieldLbl Name
lbl)) = [HieM [HieAST Type]] -> HieM [HieAST Type]
forall (m :: * -> *) a. Monad m => [m [a]] -> m [a]
concatM ([HieM [HieAST Type]] -> HieM [HieAST Type])
-> [HieM [HieAST Type]] -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ FieldLbl Name -> SrcSpan -> HieM [HieAST Type]
forall (m :: * -> *) a b.
(Monad m, Data a) =>
a -> SrcSpan -> ReaderT NodeOrigin m [HieAST b]
makeNode FieldLbl Name
lbl SrcSpan
span HieM [HieAST Type] -> [HieM [HieAST Type]] -> [HieM [HieAST Type]]
forall a. a -> [a] -> [a]
: case FieldLbl Name
lbl of
FieldLabel FastString
_ Bool
_ Name
n ->
[ Context (Located Name) -> HieM [HieAST Type]
forall a. ToHie a => a -> HieM [HieAST Type]
toHie (Context (Located Name) -> HieM [HieAST Type])
-> Context (Located Name) -> HieM [HieAST Type]
forall a b. (a -> b) -> a -> b
$ ContextInfo -> Located Name -> Context (Located Name)
forall a. ContextInfo -> a -> Context a
C (IEType -> ContextInfo
IEThing IEType
c) (Located Name -> Context (Located Name))
-> Located Name -> Context (Located Name)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L SrcSpan
span Name
n
]