Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
- type Unit = GenUnit UnitId
- unitString :: IsUnitId u => u -> String
- stringToUnit :: String -> Unit
- moduleUnit :: GenModule unit -> unit
- unhelpfulSpanFS :: UnhelpfulSpanReason -> FastString
- data ModuleName
- mkModuleName :: String -> ModuleName
- moduleName :: GenModule unit -> ModuleName
- moduleNameString :: ModuleName -> String
- data Fingerprint
- unpackFS :: FastString -> String
- readHexFingerprint :: String -> Fingerprint
- getFileHash :: FilePath -> IO Fingerprint
- data NameSpace
- data OccName
- mkOccName :: NameSpace -> String -> OccName
- nameOccName :: Name -> OccName
- occNameSpace :: OccName -> NameSpace
- occNameString :: OccName -> String
- mkVarOccFS :: FastString -> OccName
- data Name
- nameSrcSpan :: Name -> SrcSpan
- type NameCacheUpdater = NameCache
- data NameCache
- nsNames :: NameCache -> MVar OrigNameCache
- initNameCache :: Char -> [Name] -> IO NameCache
- lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name
- type Module = GenModule Unit
- mkModule :: u -> ModuleName -> GenModule u
- nameModule_maybe :: Name -> Maybe Module
- nameModule :: HasDebugCallStack => Name -> Module
- varName :: NameSpace
- isVarNameSpace :: NameSpace -> Bool
- dataName :: NameSpace
- isDataConNameSpace :: NameSpace -> Bool
- tcClsName :: NameSpace
- isTcClsNameSpace :: NameSpace -> Bool
- tvName :: NameSpace
- isTvNameSpace :: NameSpace -> Bool
- flLabel :: FieldLabel -> FieldLabelString
- data DynFlags
- defaultDynFlags :: Settings -> DynFlags
- data LlvmConfig = LlvmConfig {
- llvmTargets :: [(String, LlvmTarget)]
- llvmPasses :: [(Int, String)]
- data AvailInfo
- pattern AvailName :: Name -> AvailInfo
- pattern AvailFL :: FieldLabel -> AvailInfo
- pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo
- flSelector :: FieldLabel -> Name
- data SrcSpan
- data RealSrcSpan
- mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
- mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- mkSplitUniqSupply :: Char -> IO UniqSupply
- initSysTools :: String -> IO Settings
- type HiePath = LexicalFastString
- hiePathToFS :: HiePath -> FastString
- (<+>) :: IsLine doc => doc -> doc -> doc
- ppr :: Outputable a => a -> SDoc
- showSDoc :: DynFlags -> SDoc -> String
- hang :: SDoc -> Int -> SDoc -> SDoc
- text :: IsLine doc => String -> doc
- data FastString
- data IfaceType
- data IfaceTyCon = IfaceTyCon {}
- field_label :: FieldLabelString -> FastString
- dfs :: Ord a => AdjacencyMap a -> [a] -> [a]
- fieldNameSpace_maybe :: NameSpace -> Maybe FastString
- fieldName :: FastString -> NameSpace
- mkFastStringByteString :: ByteString -> FastString
Documentation
unitString :: IsUnitId u => u -> String #
stringToUnit :: String -> Unit #
moduleUnit :: GenModule unit -> unit #
Unit the module belongs to
Types re-exports
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
mkModuleName :: String -> ModuleName #
moduleName :: GenModule unit -> ModuleName #
Module name (e.g. A.B.C)
moduleNameString :: ModuleName -> String #
data Fingerprint #
Instances
unpackFS :: FastString -> String #
Lazily unpacks and decodes the FastString
readHexFingerprint :: String -> Fingerprint #
getFileHash :: FilePath -> IO Fingerprint #
Computes the hash of a given file. This function loops over the handle, running in constant memory.
Since: base-4.7.0.0
Occurrence Name
In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"
Instances
Data OccName | |
Defined in GHC.Types.Name.Occurrence gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName # toConstr :: OccName -> Constr # dataTypeOf :: OccName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) # gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # | |
NFData OccName | |
Defined in GHC.Types.Name.Occurrence | |
HasOccName OccName | |
Defined in GHC.Types.Name.Occurrence | |
Uniquable OccName | |
Defined in GHC.Types.Name.Occurrence | |
Binary OccName | |
Outputable OccName | |
Defined in GHC.Types.Name.Occurrence | |
OutputableBndr OccName | |
Defined in GHC.Types.Name.Occurrence pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # bndrIsJoin_maybe :: OccName -> Maybe Int # | |
Eq OccName | |
Ord OccName | |
FromField OccName Source # | |
Defined in HieDb.Types | |
ToField OccName Source # | |
Defined in HieDb.Types |
nameOccName :: Name -> OccName #
occNameSpace :: OccName -> NameSpace #
occNameString :: OccName -> String #
mkVarOccFS :: FastString -> OccName #
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
Data Name | |
Defined in GHC.Types.Name gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
NFData Name | |
Defined in GHC.Types.Name | |
NamedThing Name | |
Defined in GHC.Types.Name | |
HasOccName Name | |
Defined in GHC.Types.Name | |
Uniquable Name | |
Defined in GHC.Types.Name | |
Binary Name | Assumes that the |
Outputable Name | |
Defined in GHC.Types.Name | |
OutputableBndr Name | |
Defined in GHC.Types.Name pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
Eq Name | |
Ord Name | Caution: This instance is implemented via See |
type Anno Name | |
Defined in GHC.Hs.Extension | |
type Anno (LocatedN Name) | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN Name] | |
Defined in GHC.Hs.Binds |
nameSrcSpan :: Name -> SrcSpan #
type NameCacheUpdater = NameCache Source #
The NameCache makes sure that there is just one Unique assigned for each original name; i.e. (module-name, occ-name) pair and provides something of a lookup mechanism for those names.
nsNames :: NameCache -> MVar OrigNameCache #
lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name #
mkModule :: u -> ModuleName -> GenModule u #
nameModule_maybe :: Name -> Maybe Module #
nameModule :: HasDebugCallStack => Name -> Module #
isVarNameSpace :: NameSpace -> Bool #
isDataConNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
flLabel :: FieldLabel -> FieldLabelString #
User-visible label of the field
Dynflags re-exports
Contains not only a collection of GeneralFlag
s but also a plethora of
information relating to the compilation of a single file or GHC session
defaultDynFlags :: Settings -> DynFlags #
data LlvmConfig #
LlvmConfig | |
|
AvailInfo
Records what things are "available", i.e. in scope
Instances
Data AvailInfo | |
Defined in GHC.Types.Avail gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AvailInfo -> c AvailInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AvailInfo # toConstr :: AvailInfo -> Constr # dataTypeOf :: AvailInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AvailInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AvailInfo) # gmapT :: (forall b. Data b => b -> b) -> AvailInfo -> AvailInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> AvailInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AvailInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # | |
NFData AvailInfo | |
Defined in GHC.Types.Avail | |
Binary AvailInfo | |
Outputable AvailInfo | |
Defined in GHC.Types.Avail | |
Eq AvailInfo | Used when deciding if the interface has changed |
pattern AvailFL :: FieldLabel -> AvailInfo Source #
flSelector :: FieldLabel -> Name #
Record selector function
SrcSpan
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
Data SrcSpan | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Show SrcSpan | |
NFData SrcSpan | |
Defined in GHC.Types.SrcLoc | |
ToJson SrcSpan | |
Defined in GHC.Types.SrcLoc | |
Outputable SrcSpan | |
Defined in GHC.Types.SrcLoc | |
Eq SrcSpan | |
NamedThing e => NamedThing (Located e) | |
Defined in GHC.Types.Name | |
Outputable e => Outputable (Located e) | |
Defined in GHC.Types.SrcLoc |
data RealSrcSpan #
A RealSrcSpan
delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.
Real Source Span
Instances
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc #
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #
Create a SrcSpan
between two points in a file
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanEndCol :: RealSrcSpan -> Int #
mkSplitUniqSupply :: Char -> IO UniqSupply #
Create a unique supply out of thin air. The "mask" (Char) supplied is purely cosmetic, making it easier to figure out where a Unique was born. See Note [Uniques and masks].
The payload part of the Uniques allocated from this UniqSupply are
guaranteed distinct wrt all other supplies, regardless of their "mask".
This is achieved by allocating the payload part from
a single source of Uniques, namely genSym
, shared across
all UniqSupply's.
Systools
initSysTools :: String -> IO Settings #
Hie Types
type HiePath = LexicalFastString #
hiePathToFS :: HiePath -> FastString Source #
Outputable
(<+>) :: IsLine doc => doc -> doc -> doc #
Join two doc
s together horizontally with a gap between them.
ppr :: Outputable a => a -> SDoc #
FastString
data FastString #
A FastString
is a UTF-8 encoded string together with a unique ID. All
FastString
s are stored in a global hashtable to support fast O(1)
comparison.
It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.
Instances
IFace
A kind of universal type, used for types and kinds.
Any time a Type
is pretty-printed, it is first converted to an IfaceType
before being printed. See Note [Pretty printing via Iface syntax] in GHC.Types.TyThing.Ppr
Instances
NFData IfaceType | |
Defined in GHC.Iface.Type | |
Binary IfaceType | |
Outputable IfaceType | |
Defined in GHC.Iface.Type | |
Binary (DefMethSpec IfaceType) | |
Defined in GHC.Iface.Type |
data IfaceTyCon #
Instances
NFData IfaceTyCon | |
Defined in GHC.Iface.Type rnf :: IfaceTyCon -> () # | |
Binary IfaceTyCon | |
Defined in GHC.Iface.Type put_ :: BinHandle -> IfaceTyCon -> IO () # put :: BinHandle -> IfaceTyCon -> IO (Bin IfaceTyCon) # get :: BinHandle -> IO IfaceTyCon # | |
Outputable IfaceTyCon | |
Defined in GHC.Iface.Type ppr :: IfaceTyCon -> SDoc # | |
Eq IfaceTyCon | |
Defined in GHC.Iface.Type (==) :: IfaceTyCon -> IfaceTyCon -> Bool # (/=) :: IfaceTyCon -> IfaceTyCon -> Bool # |
dfs :: Ord a => AdjacencyMap a -> [a] -> [a] Source #
fieldName :: FastString -> NameSpace Source #
mkFastStringByteString :: ByteString -> FastString #
Create a FastString
by copying an existing ByteString