Safe Haskell | None |
---|---|
Language | Haskell2010 |
Calligraphy.Compat.GHC
Description
Thin compatability layer that re-exports things from GHC.
Synopsis
- data BindType
- data ContextInfo
- data DeclType
- data HieAST a = Node {}
- newtype HieASTs a = HieASTs {
- getAsts :: Map FastString (HieAST a)
- data HieFile = HieFile {}
- data HieFileResult = HieFileResult {}
- data HieType a
- type HieTypeFlat = HieType TypeIndex
- type Identifier = Either ModuleName Name
- data IdentifierDetails a = IdentifierDetails {
- identType :: Maybe a
- identInfo :: Set ContextInfo
- data IfaceTyCon = IfaceTyCon {}
- data ModuleName
- data Name
- data NameCache
- data NodeInfo a = NodeInfo {
- nodeAnnotations :: Set (FastString, FastString)
- nodeType :: [a]
- nodeIdentifiers :: NodeIdentifiers a
- data RealSrcLoc
- data RealSrcSpan
- data RecFieldContext
- data Scope
- type Span = RealSrcSpan
- type TypeIndex = Int
- availNames :: AvailInfo -> [Name]
- getKey :: Unique -> Int
- getOccString :: NamedThing a => a -> String
- hieVersion :: Integer
- initNameCache :: UniqSupply -> [Name] -> NameCache
- mkSplitUniqSupply :: Char -> IO UniqSupply
- moduleName :: Module -> ModuleName
- moduleNameString :: ModuleName -> String
- nameUnique :: Name -> Unique
- realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
- realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcLocCol :: RealSrcLoc -> Int
- srcLocLine :: RealSrcLoc -> Int
Documentation
Constructors
RegularBind | |
InstanceBind |
Instances
Enum BindType | |
Eq BindType | |
Ord BindType | |
Defined in HieTypes | |
Show BindType | |
Binary BindType | |
data ContextInfo #
Different contexts under which identifiers exist
Constructors
Use | regular variable |
MatchBind | |
IEThing IEType | import/export |
TyDecl | |
ValBind | Value binding |
PatternBind | Pattern binding This case is tricky because the bound identifier can be used in two
distinct scopes. Consider the following example (with do (b, a, (a -> True)) <- bar foo a The identifier |
ClassTyDecl (Maybe Span) | |
Decl | Declaration |
TyVarBind Scope TyVarScope | Type variable |
RecField RecFieldContext (Maybe Span) | Record field |
Instances
Eq ContextInfo | |
Defined in HieTypes | |
Ord ContextInfo | |
Defined in HieTypes Methods compare :: ContextInfo -> ContextInfo -> Ordering # (<) :: ContextInfo -> ContextInfo -> Bool # (<=) :: ContextInfo -> ContextInfo -> Bool # (>) :: ContextInfo -> ContextInfo -> Bool # (>=) :: ContextInfo -> ContextInfo -> Bool # max :: ContextInfo -> ContextInfo -> ContextInfo # min :: ContextInfo -> ContextInfo -> ContextInfo # | |
Show ContextInfo | |
Defined in HieTypes Methods showsPrec :: Int -> ContextInfo -> ShowS # show :: ContextInfo -> String # showList :: [ContextInfo] -> ShowS # | |
Binary ContextInfo | |
Defined in HieTypes Methods put_ :: BinHandle -> ContextInfo -> IO () # put :: BinHandle -> ContextInfo -> IO (Bin ContextInfo) # get :: BinHandle -> IO ContextInfo # | |
Outputable ContextInfo | |
Defined in HieTypes |
Constructors
FamDec | type or data family |
SynDec | type synonym |
DataDec | data declaration |
ConDec | constructor declaration |
PatSynDec | pattern synonym |
ClassDec | class declaration |
InstDec | instance declaration |
Instances
Enum DeclType | |
Eq DeclType | |
Ord DeclType | |
Defined in HieTypes | |
Show DeclType | |
Binary DeclType | |
Instances
Functor HieAST | |
Foldable HieAST | |
Defined in HieTypes Methods fold :: Monoid m => HieAST m -> m # foldMap :: Monoid m => (a -> m) -> HieAST a -> m # foldMap' :: Monoid m => (a -> m) -> HieAST a -> m # foldr :: (a -> b -> b) -> b -> HieAST a -> b # foldr' :: (a -> b -> b) -> b -> HieAST a -> b # foldl :: (b -> a -> b) -> b -> HieAST a -> b # foldl' :: (b -> a -> b) -> b -> HieAST a -> b # foldr1 :: (a -> a -> a) -> HieAST a -> a # foldl1 :: (a -> a -> a) -> HieAST a -> a # elem :: Eq a => a -> HieAST a -> Bool # maximum :: Ord a => HieAST a -> a # minimum :: Ord a => HieAST a -> a # | |
Traversable HieAST | |
Binary (HieAST TypeIndex) | |
Mapping from filepaths (represented using FastString
) to the
corresponding AST
Constructors
HieASTs | |
Fields
|
Instances
Functor HieASTs | |
Foldable HieASTs | |
Defined in HieTypes Methods fold :: Monoid m => HieASTs m -> m # foldMap :: Monoid m => (a -> m) -> HieASTs a -> m # foldMap' :: Monoid m => (a -> m) -> HieASTs a -> m # foldr :: (a -> b -> b) -> b -> HieASTs a -> b # foldr' :: (a -> b -> b) -> b -> HieASTs a -> b # foldl :: (b -> a -> b) -> b -> HieASTs a -> b # foldl' :: (b -> a -> b) -> b -> HieASTs a -> b # foldr1 :: (a -> a -> a) -> HieASTs a -> a # foldl1 :: (a -> a -> a) -> HieASTs a -> a # elem :: Eq a => a -> HieASTs a -> Bool # maximum :: Ord a => HieASTs a -> a # minimum :: Ord a => HieASTs a -> a # | |
Traversable HieASTs | |
Binary (HieASTs TypeIndex) | |
GHC builds up a wealth of information about Haskell source as it compiles it.
.hie
files are a way of persisting some of this information to disk so that
external tools that need to work with haskell source don't need to parse,
typecheck, and rename all over again. These files contain:
a simplified AST
- nodes are annotated with source positions and types
- identifiers are annotated with scope information
- the raw bytes of the initial Haskell source
Besides saving compilation cycles, .hie
files also offer a more stable
interface than the GHC API.
Constructors
HieFile | |
Fields
|
data HieFileResult #
Constructors
HieFileResult | |
A flattened version of Type
.
See Note [Efficient serialization of redundant type info]
Constructors
HTyVarTy Name | |
HAppTy a (HieArgs a) | |
HTyConApp IfaceTyCon (HieArgs a) | |
HForAllTy ((Name, a), ArgFlag) a | |
HFunTy a a | |
HQualTy a a | type with constraint: |
HLitTy IfaceTyLit | |
HCastTy a | |
HCoercionTy |
Instances
Functor HieType | |
Foldable HieType | |
Defined in HieTypes Methods fold :: Monoid m => HieType m -> m # foldMap :: Monoid m => (a -> m) -> HieType a -> m # foldMap' :: Monoid m => (a -> m) -> HieType a -> m # foldr :: (a -> b -> b) -> b -> HieType a -> b # foldr' :: (a -> b -> b) -> b -> HieType a -> b # foldl :: (b -> a -> b) -> b -> HieType a -> b # foldl' :: (b -> a -> b) -> b -> HieType a -> b # foldr1 :: (a -> a -> a) -> HieType a -> a # foldl1 :: (a -> a -> a) -> HieType a -> a # elem :: Eq a => a -> HieType a -> Bool # maximum :: Ord a => HieType a -> a # minimum :: Ord a => HieType a -> a # | |
Traversable HieType | |
Eq a => Eq (HieType a) | |
Binary (HieType TypeIndex) | |
type HieTypeFlat = HieType TypeIndex #
type Identifier = Either ModuleName Name #
data IdentifierDetails a #
Information associated with every identifier
We need to include types with identifiers because sometimes multiple identifiers occur in the same span(Overloaded Record Fields and so on)
Constructors
IdentifierDetails | |
Fields
|
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 |
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
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 |
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.
The information stored in one AST node.
The type parameter exists to provide flexibility in representation of types (see Note [Efficient serialization of redundant type info]).
Constructors
NodeInfo | |
Fields
|
Instances
Functor NodeInfo | |
Foldable NodeInfo | |
Defined in HieTypes Methods fold :: Monoid m => NodeInfo m -> m # foldMap :: Monoid m => (a -> m) -> NodeInfo a -> m # foldMap' :: Monoid m => (a -> m) -> NodeInfo a -> m # foldr :: (a -> b -> b) -> b -> NodeInfo a -> b # foldr' :: (a -> b -> b) -> b -> NodeInfo a -> b # foldl :: (b -> a -> b) -> b -> NodeInfo a -> b # foldl' :: (b -> a -> b) -> b -> NodeInfo a -> b # foldr1 :: (a -> a -> a) -> NodeInfo a -> a # foldl1 :: (a -> a -> a) -> NodeInfo a -> a # elem :: Eq a => a -> NodeInfo a -> Bool # maximum :: Ord a => NodeInfo a -> a # minimum :: Ord a => NodeInfo a -> a # | |
Traversable NodeInfo | |
Binary (NodeInfo TypeIndex) | |
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
Eq RealSrcLoc | |
Defined in SrcLoc | |
Ord RealSrcLoc | |
Defined in SrcLoc Methods compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
Show RealSrcLoc | |
Defined in SrcLoc Methods showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc | |
Defined in 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
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 |
data RecFieldContext #
Constructors
RecFieldDecl | |
RecFieldAssign | |
RecFieldMatch | |
RecFieldOcc |
Instances
Constructors
NoScope | |
LocalScope Span | |
ModuleScope |
Instances
Eq Scope | |
Data Scope | |
Defined in HieTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scope -> c Scope # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scope # dataTypeOf :: Scope -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scope) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope) # gmapT :: (forall b. Data b => b -> b) -> Scope -> Scope # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r # gmapQ :: (forall d. Data d => d -> u) -> Scope -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scope -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scope -> m Scope # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scope -> m Scope # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scope -> m Scope # | |
Ord Scope | |
Show Scope | |
Binary Scope | |
Outputable Scope | |
type Span = RealSrcSpan #
availNames :: AvailInfo -> [Name] #
All names made available by the availability information (excluding overloaded selectors)
getOccString :: NamedThing a => a -> String #
hieVersion :: Integer #
Current version of .hie
files
initNameCache :: UniqSupply -> [Name] -> NameCache #
Return a function to atomically update the name cache.
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.
moduleName :: Module -> ModuleName #
moduleNameString :: ModuleName -> String #
nameUnique :: Name -> Unique #
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanEndCol :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcLocCol :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocLine :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc