| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
HieDb.Compat
Synopsis
- nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
- type Unit = UnitId
- unitString :: Unit -> String
- stringToUnit :: String -> Unit
- moduleUnit :: Module -> Unit
- unhelpfulSpanFS :: FastString -> FastString
- data ModuleName
- mkModuleName :: String -> ModuleName
- moduleName :: Module -> 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
- newtype NameCacheUpdater = NCU {- updateNameCache :: forall c. (NameCache -> (NameCache, c)) -> IO c
 
- data NameCache
- nsNames :: NameCache -> OrigNameCache
- initNameCache :: UniqSupply -> [Name] -> NameCache
- lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name
- data Module
- mkModule :: UnitId -> ModuleName -> Module
- 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 :: FieldLbl a -> FieldLabelString
- data DynFlags
- defaultDynFlags :: Settings -> LlvmConfig -> 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 :: FieldLbl a -> a
- 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 = FastString
- hiePathToFS :: HiePath -> FastString
- (<+>) :: SDoc -> SDoc -> SDoc
- ppr :: Outputable a => a -> SDoc
- showSDoc :: DynFlags -> SDoc -> String
- hang :: SDoc -> Int -> SDoc -> SDoc
- text :: String -> SDoc
- data FastString
- data IfaceType
- data IfaceTyCon = IfaceTyCon {}
Documentation
unitString :: Unit -> String Source #
stringToUnit :: String -> Unit Source #
moduleUnit :: Module -> Unit Source #
Types re-exports
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List.
Instances
mkModuleName :: String -> ModuleName #
moduleName :: Module -> ModuleName #
moduleNameString :: ModuleName -> String #
data Fingerprint #
Instances
| Eq Fingerprint | Since: base-4.4.0.0 | 
| Defined in GHC.Fingerprint.Type | |
| Ord Fingerprint | Since: base-4.4.0.0 | 
| Defined in GHC.Fingerprint.Type Methods compare :: Fingerprint -> Fingerprint -> Ordering # (<) :: Fingerprint -> Fingerprint -> Bool # (<=) :: Fingerprint -> Fingerprint -> Bool # (>) :: Fingerprint -> Fingerprint -> Bool # (>=) :: Fingerprint -> Fingerprint -> Bool # max :: Fingerprint -> Fingerprint -> Fingerprint # min :: Fingerprint -> Fingerprint -> Fingerprint # | |
| Show Fingerprint | Since: base-4.7.0.0 | 
| Defined in GHC.Fingerprint.Type Methods showsPrec :: Int -> Fingerprint -> ShowS # show :: Fingerprint -> String # showList :: [Fingerprint] -> ShowS # | |
| Outputable Fingerprint | |
| Defined in Outputable | |
| Hashable Fingerprint | Since: hashable-1.3.0.0 | 
| Defined in Data.Hashable.Class | |
| FromField Fingerprint Source # | |
| Defined in HieDb.Types Methods | |
| ToField Fingerprint Source # | |
| Defined in HieDb.Types Methods toField :: Fingerprint -> SQLData # | |
unpackFS :: FastString -> String #
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
Instances
| Eq NameSpace | |
| Ord NameSpace | |
| Binary NameSpace | |
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
| Eq OccName | |
| Data OccName | |
| Defined in OccName Methods 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 # | |
| Ord OccName | |
| NFData OccName | |
| HasOccName OccName | |
| Binary OccName | |
| Uniquable OccName | |
| Outputable OccName | |
| OutputableBndr OccName | |
| Defined in OccName Methods pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # bndrIsJoin_maybe :: OccName -> Maybe Int # | |
| FromField OccName Source # | |
| Defined in HieDb.Types Methods | |
| 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
| Eq Name | |
| Data Name | |
| Defined in Name Methods 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 # | |
| Ord Name | Caution: This instance is implemented via  See  | 
| NFData Name | |
| NamedThing Name | |
| HasOccName Name | |
| Binary Name | Assumes that the  | 
| Uniquable Name | |
| HasSrcSpan Name | |
| Defined in Name Methods composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
| Outputable Name | |
| OutputableBndr Name | |
| Defined in Name Methods pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
| type SrcSpanLess Name | |
| Defined in Name | |
nameSrcSpan :: Name -> SrcSpan #
newtype NameCacheUpdater #
A function that atomically updates the name cache given a modifier function. The second result of the modifier function will be the result of the IO action.
Constructors
| NCU | |
| Fields 
 | |
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 -> OrigNameCache #
Ensures that one original name gets one unique
initNameCache :: UniqSupply -> [Name] -> NameCache #
Return a function to atomically update the name cache.
lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name #
A Module is a pair of a UnitId and a ModuleName.
Module variables (i.e. H) which can be instantiated to a
 specific module at some later point in time are represented
 with moduleUnitId set to holeUnitId (this allows us to
 avoid having to make moduleUnitId a partial operation.)
Instances
mkModule :: UnitId -> ModuleName -> Module #
nameModule_maybe :: Name -> Maybe Module #
nameModule :: HasDebugCallStack => Name -> Module #
isVarNameSpace :: NameSpace -> Bool #
isDataConNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
flLabel :: FieldLbl a -> FieldLabelString #
User-visible label of the field
Dynflags re-exports
Contains not only a collection of GeneralFlags but also a plethora of
 information relating to the compilation of a single file or GHC session
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags #
data LlvmConfig #
See Note [LLVM Configuration] in SysTools.
Constructors
| LlvmConfig | |
| Fields 
 | |
AvailInfo
Records what things are "available", i.e. in scope
Instances
| Eq AvailInfo | Used when deciding if the interface has changed | 
| Data AvailInfo | |
| Defined in Avail Methods 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 # | |
| Binary AvailInfo | |
| Outputable AvailInfo | |
pattern AvailFL :: FieldLabel -> AvailInfo Source #
flSelector :: FieldLbl a -> a #
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.
Constructors
| RealSrcSpan !RealSrcSpan | |
| UnhelpfulSpan !FastString | 
Instances
| Eq SrcSpan | |
| Data SrcSpan | |
| Defined in SrcLoc Methods 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 # | |
| Ord SrcSpan | |
| Show SrcSpan | |
| NFData SrcSpan | |
| ToJson SrcSpan | |
| Outputable SrcSpan | |
| NamedThing e => NamedThing (Located e) | |
| HasSrcSpan (Located a) | |
| Defined in SrcLoc Methods composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
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
| Eq RealSrcSpan | |
| Defined in SrcLoc | |
| Data RealSrcSpan | |
| Defined in SrcLoc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RealSrcSpan -> c RealSrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RealSrcSpan # toConstr :: RealSrcSpan -> Constr # dataTypeOf :: RealSrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RealSrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RealSrcSpan) # gmapT :: (forall b. Data b => b -> b) -> RealSrcSpan -> RealSrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> RealSrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RealSrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan # | |
| Ord RealSrcSpan | |
| Defined in SrcLoc Methods compare :: RealSrcSpan -> RealSrcSpan -> Ordering # (<) :: RealSrcSpan -> RealSrcSpan -> Bool # (<=) :: RealSrcSpan -> RealSrcSpan -> Bool # (>) :: RealSrcSpan -> RealSrcSpan -> Bool # (>=) :: RealSrcSpan -> RealSrcSpan -> Bool # max :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan # min :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan # | |
| Show RealSrcSpan | |
| Defined in SrcLoc Methods showsPrec :: Int -> RealSrcSpan -> ShowS # show :: RealSrcSpan -> String # showList :: [RealSrcSpan] -> ShowS # | |
| ToJson RealSrcSpan | |
| Defined in SrcLoc Methods json :: RealSrcSpan -> JsonDoc # | |
| Outputable RealSrcSpan | |
| Defined in SrcLoc | |
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 character given must be distinct from those of all calls to this function in the compiler for the values generated to be truly unique.
Systools
initSysTools :: String -> IO Settings #
Hie Types
type HiePath = FastString Source #
hiePathToFS :: HiePath -> FastString Source #
Outputable
ppr :: Outputable a => a -> SDoc #
FastString
data FastString #
A FastString is a UTF-8 encoded string together with a unique ID. All
FastStrings 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 IfaceSyn] in PprTyThing
Instances
data IfaceTyCon #
Constructors
| IfaceTyCon | |
| Fields | |
Instances
| Eq IfaceTyCon | |
| Defined in IfaceType | |
| NFData IfaceTyCon | |
| Defined in IfaceType Methods rnf :: IfaceTyCon -> () # | |
| Binary IfaceTyCon | |
| Defined in IfaceType Methods put_ :: BinHandle -> IfaceTyCon -> IO () # put :: BinHandle -> IfaceTyCon -> IO (Bin IfaceTyCon) # get :: BinHandle -> IO IfaceTyCon # | |
| Outputable IfaceTyCon | |
| Defined in IfaceType | |