hiedb-0.4.2.0: Generates a references DB from .hie files
Safe HaskellSafe-Inferred
LanguageHaskell2010

HieDb.Compat

Synopsis

Documentation

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

Instances details
Data ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName #

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) #

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

Show ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

NFData ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

rnf :: ModuleName -> () #

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Binary ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Outputable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc #

Eq ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Ord ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

FromField ModuleName Source # 
Instance details

Defined in HieDb.Types

FromRow ModuleName Source # 
Instance details

Defined in HieDb.Types

ToField ModuleName Source # 
Instance details

Defined in HieDb.Types

type Anno ModuleName 
Instance details

Defined in GHC.Hs.ImpExp

moduleName :: GenModule unit -> ModuleName #

Module name (e.g. A.B.C)

data Fingerprint #

Instances

Instances details
Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type #

Show Fingerprint

Since: base-4.7.0.0

Instance details

Defined in GHC.Fingerprint.Type

Outputable Fingerprint 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Fingerprint -> SDoc #

Eq Fingerprint

Since: base-4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Ord Fingerprint

Since: base-4.4.0.0

Instance details

Defined in GHC.Fingerprint.Type

Hashable Fingerprint

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

FromField Fingerprint Source # 
Instance details

Defined in HieDb.Types

ToField Fingerprint Source # 
Instance details

Defined in HieDb.Types

type Rep Fingerprint

Since: base-4.15.0.0

Instance details

Defined in GHC.Generics

type Rep Fingerprint = D1 ('MetaData "Fingerprint" "GHC.Fingerprint.Type" "base" 'False) (C1 ('MetaCons "Fingerprint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))

unpackFS :: FastString -> String #

Unpacks and decodes the FastString

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

data OccName #

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

Instances details
Data OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

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 #

NFData OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Binary OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc #

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Eq OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

(==) :: OccName -> OccName -> Bool #

(/=) :: OccName -> OccName -> Bool #

Ord OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

FromField OccName Source # 
Instance details

Defined in HieDb.Types

ToField OccName Source # 
Instance details

Defined in HieDb.Types

Methods

toField :: OccName -> SQLData #

data Name #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Instances details
Data Name 
Instance details

Defined in GHC.Types.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 #

toConstr :: Name -> Constr #

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 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () #

NamedThing Name 
Instance details

Defined in GHC.Types.Name

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Binary Name

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in GHC.Types.Name

Methods

put_ :: BinHandle -> Name -> IO () #

put :: BinHandle -> Name -> IO (Bin Name) #

get :: BinHandle -> IO Name #

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc #

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

Eq Name

The same comments as for Name's Ord instance apply.

Instance details

Defined in GHC.Types.Name

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name

Caution: This instance is implemented via nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and trac #15240 for a bug caused by improper use of this instance.

Instance details

Defined in GHC.Types.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

type Anno Name 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

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

data NameCache #

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.

type Module = GenModule Unit #

A Module is a pair of a Unit and a ModuleName.

flLabel :: FieldLabel -> FieldLabelString #

User-visible label of the field

Dynflags re-exports

data DynFlags #

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 #

The normal DynFlags. Note that they are not suitable for use in this form and must be fully initialized by runGhc first.

data LlvmConfig #

See Note [LLVM Configuration] in GHC.SysTools.

Constructors

LlvmConfig 

AvailInfo

data AvailInfo #

Records what things are "available", i.e. in scope

Instances

Instances details
Data AvailInfo 
Instance details

Defined in GHC.Types.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 
Instance details

Defined in GHC.Types.Avail

Outputable AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc #

Eq AvailInfo

Used when deciding if the interface has changed

Instance details

Defined in GHC.Types.Avail

pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo Source #

flSelector :: FieldLabel -> Name #

Record selector function

SrcSpan

data SrcSpan #

Source Span

A SrcSpan identifies either a specific portion of a text file or a human-readable description of a location.

Instances

Instances details
Data SrcSpan 
Instance details

Defined in GHC.Types.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 #

Show SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () #

ToJson SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

Eq SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

(==) :: SrcSpan -> SrcSpan -> Bool #

(/=) :: SrcSpan -> SrcSpan -> Bool #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) 
Instance details

Defined in Language.Haskell.Syntax.Type

data RealSrcSpan #

A SrcSpan 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

Instances details
Data RealSrcSpan 
Instance details

Defined in GHC.Types.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 #

Show RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

ToJson RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc #

Outputable RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc #

Eq RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Outputable e => Outputable (GenLocated RealSrcSpan e) 
Instance details

Defined in GHC.Types.SrcLoc

mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #

Create a SrcSpan between two points in a file

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

Hie Types

Outputable

(<+>) :: SDoc -> SDoc -> SDoc #

Join two SDoc together horizontally with a gap between them

ppr :: Outputable a => a -> SDoc #

showSDoc :: DynFlags -> SDoc -> String #

Show a SDoc as a String with the default user style

hang #

Arguments

:: SDoc

The header

-> Int

Amount to indent the hung body

-> SDoc

The hung body, indented and placed below the header

-> 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

Instances details
Data FastString 
Instance details

Defined in GHC.Data.FastString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FastString -> c FastString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FastString #

toConstr :: FastString -> Constr #

dataTypeOf :: FastString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FastString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FastString) #

gmapT :: (forall b. Data b => b -> b) -> FastString -> FastString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FastString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FastString -> r #

gmapQ :: (forall d. Data d => d -> u) -> FastString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FastString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

IsString FastString 
Instance details

Defined in GHC.Data.FastString

Monoid FastString 
Instance details

Defined in GHC.Data.FastString

Semigroup FastString 
Instance details

Defined in GHC.Data.FastString

Show FastString 
Instance details

Defined in GHC.Data.FastString

NFData FastString 
Instance details

Defined in GHC.Data.FastString

Methods

rnf :: FastString -> () #

Uniquable FastString 
Instance details

Defined in GHC.Types.Unique

Outputable FastString 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc #

Eq FastString 
Instance details

Defined in GHC.Data.FastString

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

IFace

data IfaceType #

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

Instances details
NFData IfaceType 
Instance details

Defined in GHC.Iface.Type

Methods

rnf :: IfaceType -> () #

Binary IfaceType 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceType 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceType -> SDoc #

Binary (DefMethSpec IfaceType) 
Instance details

Defined in GHC.Iface.Type

data IfaceTyCon #

Instances

Instances details
NFData IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

rnf :: IfaceTyCon -> () #

Binary IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyCon -> SDoc #

Eq IfaceTyCon 
Instance details

Defined in GHC.Iface.Type