| Copyright | (c) 2020 Kowainik |
|---|---|
| License | MPL-2.0 |
| Maintainer | Kowainik <xrom.xkov@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Stan.Ghc.Compat
Description
Compatibility module for GHC types and functions. Reexports all required API to work with the GHC API.
Synopsis
- data Module
- data ModuleName
- moduleNameString :: ModuleName -> String
- moduleName :: Module -> ModuleName
- moduleStableString :: Module -> String
- moduleUnitId :: Module -> UnitId
- data Name
- isExternalName :: Name -> Bool
- isSymOcc :: OccName -> Bool
- nameModule :: HasDebugCallStack => Name -> Module
- nameOccName :: Name -> OccName
- nameStableString :: Name -> String
- occNameString :: OccName -> String
- data RealSrcSpan
- srcSpanEndCol :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanFile :: RealSrcSpan -> FastString
- data ArgFlag
- data AvailInfo
- data FastString
- data FieldLbl a = FieldLabel {
- flLabel :: FieldLabelString
- flIsOverloaded :: Bool
- flSelector :: a
- data IfaceTyCon = IfaceTyCon {}
- data IfaceTyConInfo = IfaceTyConInfo {}
- data IfaceTyConSort
- data IfaceTyLit
- data PromotionFlag
- data TupleSort
Modules
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
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List.
Instances
moduleNameString :: ModuleName -> String #
moduleName :: Module -> ModuleName #
moduleStableString :: Module -> String #
Get a string representation of a Module that's unique and stable
across recompilations.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"
moduleUnitId :: Module -> UnitId #
Names
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 |
| Show Name Source # | |
| 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 | |
isExternalName :: Name -> Bool #
Test if the OccName is that for any operator (whether
it is a data constructor or variable or whatever)
nameModule :: HasDebugCallStack => Name -> Module #
nameOccName :: Name -> OccName #
nameStableString :: Name -> String #
Get a string representation of a Name that's unique and stable
across recompilations. Used for deterministic generation of binds for
derived instances.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"
occNameString :: OccName -> String #
Source locations
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 | |
srcSpanEndCol :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanFile :: RealSrcSpan -> FastString #
Other common types (for debugging and not only)
Argument Flag
Is something required to appear in source Haskell (Required),
permitted by request (Specified) (visible type application), or
prohibited entirely from appearing in source Haskell (Inferred)?
See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep
Instances
| Eq ArgFlag | |
| Data ArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgFlag -> c ArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgFlag # toConstr :: ArgFlag -> Constr # dataTypeOf :: ArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgFlag) # gmapT :: (forall b. Data b => b -> b) -> ArgFlag -> ArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # | |
| Ord ArgFlag | |
| Show ArgFlag Source # | |
| Binary ArgFlag | |
| Outputable ArgFlag | |
| Outputable tv => Outputable (VarBndr tv ArgFlag) | |
Records what things are "available", i.e. in scope
Constructors
| Avail Name | An ordinary identifier in scope |
| AvailTC | A type or class in scope The AvailTC Invariant: If the type or class is itself to be in scope, it must be first in this list. Thus, typically: AvailTC Eq [Eq, ==, \/=] [] |
Fields
| |
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 # | |
| Show AvailInfo Source # | |
| Binary AvailInfo | |
| Outputable AvailInfo | |
data FastString #
A FastString is an array of bytes, hashed to support fast O(1)
comparison. It is also associated with a character encoding, so that
we know how to convert a FastString to the local encoding, or to the
Z-encoding used by the compiler internally.
FastStrings support a memoized conversion to the Z-encoding via zEncodeFS.
Instances
Fields in an algebraic record type
Constructors
| FieldLabel | |
Fields
| |
Instances
| Functor FieldLbl | |
| Foldable FieldLbl | |
Defined in FieldLabel Methods fold :: Monoid m => FieldLbl m -> m # foldMap :: Monoid m => (a -> m) -> FieldLbl a -> m # foldMap' :: Monoid m => (a -> m) -> FieldLbl a -> m # foldr :: (a -> b -> b) -> b -> FieldLbl a -> b # foldr' :: (a -> b -> b) -> b -> FieldLbl a -> b # foldl :: (b -> a -> b) -> b -> FieldLbl a -> b # foldl' :: (b -> a -> b) -> b -> FieldLbl a -> b # foldr1 :: (a -> a -> a) -> FieldLbl a -> a # foldl1 :: (a -> a -> a) -> FieldLbl a -> a # elem :: Eq a => a -> FieldLbl a -> Bool # maximum :: Ord a => FieldLbl a -> a # minimum :: Ord a => FieldLbl a -> a # | |
| Traversable FieldLbl | |
| Eq a => Eq (FieldLbl a) | |
| Data a => Data (FieldLbl a) | |
Defined in FieldLabel Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLbl a -> c (FieldLbl a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLbl a) # toConstr :: FieldLbl a -> Constr # dataTypeOf :: FieldLbl a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLbl a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLbl a)) # gmapT :: (forall b. Data b => b -> b) -> FieldLbl a -> FieldLbl a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLbl a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLbl a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # | |
| Show a => Show (FieldLbl a) Source # | |
| Binary a => Binary (FieldLbl a) | |
| Outputable a => Outputable (FieldLbl a) | |
data IfaceTyCon #
Constructors
| IfaceTyCon | |
Fields | |
Instances
| Eq IfaceTyCon | |
Defined in IfaceType | |
| Show IfaceTyCon Source # | |
Defined in Stan.Hie.Debug Methods showsPrec :: Int -> IfaceTyCon -> ShowS # show :: IfaceTyCon -> String # showList :: [IfaceTyCon] -> ShowS # | |
| 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 IfaceTyConInfo #
Constructors
| IfaceTyConInfo | |
Instances
| Eq IfaceTyConInfo | |
Defined in IfaceType Methods (==) :: IfaceTyConInfo -> IfaceTyConInfo -> Bool # (/=) :: IfaceTyConInfo -> IfaceTyConInfo -> Bool # | |
| Show IfaceTyConInfo Source # | |
Defined in Stan.Hie.Debug Methods showsPrec :: Int -> IfaceTyConInfo -> ShowS # show :: IfaceTyConInfo -> String # showList :: [IfaceTyConInfo] -> ShowS # | |
| Binary IfaceTyConInfo | |
Defined in IfaceType Methods put_ :: BinHandle -> IfaceTyConInfo -> IO () # put :: BinHandle -> IfaceTyConInfo -> IO (Bin IfaceTyConInfo) # get :: BinHandle -> IO IfaceTyConInfo # | |
data IfaceTyConSort #
The various types of TyCons which have special, built-in syntax.
Constructors
| IfaceNormalTyCon | a regular tycon |
| IfaceTupleTyCon !Arity !TupleSort | e.g. |
| IfaceSumTyCon !Arity | e.g. |
| IfaceEqualityTyCon | A heterogeneous equality TyCon (i.e. eqPrimTyCon, eqReprPrimTyCon, heqTyCon) that is actually being applied to two types of the same kind. This affects pretty-printing only: see Note [Equality predicates in IfaceType] |
Instances
| Eq IfaceTyConSort | |
Defined in IfaceType Methods (==) :: IfaceTyConSort -> IfaceTyConSort -> Bool # (/=) :: IfaceTyConSort -> IfaceTyConSort -> Bool # | |
| Show IfaceTyConSort Source # | |
Defined in Stan.Hie.Debug Methods showsPrec :: Int -> IfaceTyConSort -> ShowS # show :: IfaceTyConSort -> String # showList :: [IfaceTyConSort] -> ShowS # | |
| Binary IfaceTyConSort | |
Defined in IfaceType Methods put_ :: BinHandle -> IfaceTyConSort -> IO () # put :: BinHandle -> IfaceTyConSort -> IO (Bin IfaceTyConSort) # get :: BinHandle -> IO IfaceTyConSort # | |
data IfaceTyLit #
Constructors
| IfaceNumTyLit Integer | |
| IfaceStrTyLit FastString |
Instances
| Eq IfaceTyLit | |
Defined in IfaceType | |
| Show IfaceTyLit Source # | |
Defined in Stan.Hie.Debug Methods showsPrec :: Int -> IfaceTyLit -> ShowS # show :: IfaceTyLit -> String # showList :: [IfaceTyLit] -> ShowS # | |
| Binary IfaceTyLit | |
Defined in IfaceType Methods put_ :: BinHandle -> IfaceTyLit -> IO () # put :: BinHandle -> IfaceTyLit -> IO (Bin IfaceTyLit) # get :: BinHandle -> IO IfaceTyLit # | |
| Outputable IfaceTyLit | |
Defined in IfaceType | |
data PromotionFlag #
Is a TyCon a promoted data constructor or just a normal type constructor?
Constructors
| NotPromoted | |
| IsPromoted |
Instances
| Eq PromotionFlag | |
Defined in BasicTypes Methods (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
| Data PromotionFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # | |
| Show PromotionFlag Source # | |
Defined in Stan.Hie.Debug Methods showsPrec :: Int -> PromotionFlag -> ShowS # show :: PromotionFlag -> String # showList :: [PromotionFlag] -> ShowS # | |
Constructors
| BoxedTuple | |
| UnboxedTuple | |
| ConstraintTuple |
Instances
| Eq TupleSort | |
| Data TupleSort | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleSort -> c TupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort # toConstr :: TupleSort -> Constr # dataTypeOf :: TupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # | |
| Show TupleSort Source # | |