|
|
|
|
|
Description |
Abstract syntax of global declarations.
Definitions for: TyDecl and ConDecl, ClassDecl,
InstDecl, DefaultDecl and ForeignDecl.
|
|
Synopsis |
|
|
|
|
Toplevel declarations
|
|
|
A Haskell Declaration
| Constructors | | Instances | |
|
|
|
|
Class or type declarations
|
|
|
A type or class declaration.
| Constructors | ForeignType | | | TyFamily | type/data family T :: *->* | | TyData | Declares a data type or newtype, giving its construcors
data/newtype T a = constrs
data/newtype instance T [a] = constrs
| tcdND :: NewOrData | | tcdCtxt :: LHsContext name | Context
| tcdLName :: Located name | | tcdTyVars :: [LHsTyVarBndr name] | | tcdTyPats :: Maybe [LHsType name] | Type patterns.
Just [t1..tn] for data instance T t1..tn = ...
in this case tcdTyVars = fv( tcdTyPats ).
Nothing for everything else.
| tcdKindSig :: Maybe Kind | Optional kind signature.
(Just k) for a GADT-style data, or data
instance decl with explicit kind sig
| tcdCons :: [LConDecl name] | Data constructors
For data T a = T1 | T2 a
the LConDecls all have ResTyH98.
For data T a where { T1 :: T a }
the LConDecls all have ResTyGADT.
| tcdDerivs :: Maybe [LHsType name] | Derivings; Nothing => not specified,
Just [] => derive exactly what is asked
These types must be of form
forall ab. C ty1 ty2
Typically the foralls and ty args are empty, but they
are non-empty for the newtype-deriving case
|
| TySynonym | | tcdLName :: Located name | | tcdTyVars :: [LHsTyVarBndr name] | | tcdTyPats :: Maybe [LHsType name] | Type patterns.
Just [t1..tn] for data instance T t1..tn = ...
in this case tcdTyVars = fv( tcdTyPats ).
Nothing for everything else.
| tcdSynRhs :: LHsType name | synonym expansion
|
| ClassDecl | | |
| Instances | |
|
|
|
|
|
type class
|
|
|
vanilla Haskell type synonym (ie, not a type instance)
|
|
|
True = argument is a data/newtype or data/newtype instance
declaration.
|
|
|
type or type instance declaration
|
|
|
type family declaration
|
|
|
family instance (types, newtypes, and data types)
|
|
|
|
|
Returns all the binding names of the decl, along with their SrcLocs.
The first one is guaranteed to be the name of the decl. For record fields
mentioned in multiple constructors, the SrcLoc will be from the first
occurence. We use the equality to filter out duplicate field names
|
|
|
|
|
|
Instance declarations
|
|
|
Constructors | | Instances | |
|
|
|
|
|
Constructors | NewType | newtype Blah ... | DataType | data Blah ... |
| Instances | |
|
|
|
Constructors | TypeFamily | type family ... | DataFamily | data family ... |
|
|
|
|
|
Standalone deriving declarations
|
|
|
Constructors | | Instances | |
|
|
|
|
RULE declarations
|
|
|
Constructors | | Instances | |
|
|
|
|
|
Constructors | | Instances | |
|
|
|
|
default declarations
|
|
|
Constructors | | Instances | |
|
|
|
|
Top-level template haskell splice
|
|
|
Constructors | | Instances | |
|
|
Foreign function interface declarations
|
|
|
Constructors | | Instances | |
|
|
|
|
|
Constructors | | Instances | |
|
|
|
Constructors | | Instances | |
|
|
|
|
|
Data-constructor declarations
|
|
|
Constructors | ConDecl | | con_name :: Located name | Constructor name. This is used for the DataCon itself, and for
the user-callable wrapper Id.
| con_explicit :: HsExplicitForAll | Is there an user-written forall? (cf. HsForAllTy)
| con_qvars :: [LHsTyVarBndr name] | Type variables. Depending on con_res this describes the
follewing entities
- ResTyH98: the constructor's *existential* type variables
- ResTyGADT: *all* the constructor's quantified type variables
| con_cxt :: LHsContext name | The context. This does not include the "stupid theta" which
lives only in the TyData decl.
| con_details :: HsConDeclDetails name | The main payload
| con_res :: ResType name | Result type of the constructor
| con_doc :: Maybe LHsDocString | A possible Haddock comment.
| con_old_rec :: Bool | TEMPORARY field; True = user has employed now-deprecated syntax for
GADT-style record decl C { blah } :: T a b
Remove this when we no longer parse this stuff, and hence do not
need to report decprecated use
|
|
| Instances | |
|
|
|
|
|
Constructors | | Instances | |
|
|
|
|
|
|
|
|
Document comments
|
|
|
Constructors | | Instances | |
|
|
|
|
|
|
Deprecations
|
|
|
Constructors | | Instances | |
|
|
|
|
Annotations
|
|
|
Constructors | | Instances | |
|
|
|
|
data AnnProvenance name | Source |
|
Constructors | ValueAnnProvenance name | | TypeAnnProvenance name | | ModuleAnnProvenance | |
|
|
|
|
|
|
|
Grouping
|
|
|
A HsDecl is categorised into a HsGroup before being
fed to the renamer.
| Constructors | | Instances | |
|
|
|
|
|
|
|
|
Produced by Haddock version 2.6.1 |