Safe Haskell | None |
---|---|
Language | Haskell98 |
Data types for modules and declarations
- data Module = Module SourceSpan [Comment] ModuleName [Declaration] (Maybe [DeclarationRef])
- getModuleName :: Module -> ModuleName
- addDefaultImport :: ModuleName -> Module -> Module
- data DeclarationRef
- isModuleRef :: DeclarationRef -> Bool
- findDuplicateRefs :: [DeclarationRef] -> ([DeclarationRef], [ProperName ConstructorName])
- data ImportDeclarationType
- isImplicit :: ImportDeclarationType -> Bool
- isExplicit :: ImportDeclarationType -> Bool
- data Declaration
- = DataDeclaration DataDeclType (ProperName TypeName) [(String, Maybe Kind)] [(ProperName ConstructorName, [Type])]
- | DataBindingGroupDeclaration [Declaration]
- | TypeSynonymDeclaration (ProperName TypeName) [(String, Maybe Kind)] Type
- | TypeDeclaration Ident Type
- | ValueDeclaration Ident NameKind [Binder] (Either [(Guard, Expr)] Expr)
- | BindingGroupDeclaration [(Ident, NameKind, Expr)]
- | ExternDeclaration Ident Type
- | ExternDataDeclaration (ProperName TypeName) Kind
- | FixityDeclaration Fixity String (Maybe (Either (Qualified Ident) (Qualified (ProperName ConstructorName))))
- | ImportDeclaration ModuleName ImportDeclarationType (Maybe ModuleName) Bool
- | TypeClassDeclaration (ProperName ClassName) [(String, Maybe Kind)] [Constraint] [Declaration]
- | TypeInstanceDeclaration Ident [Constraint] (Qualified (ProperName ClassName)) [Type] TypeInstanceBody
- | PositionedDeclaration SourceSpan [Comment] Declaration
- data TypeInstanceBody
- mapTypeInstanceBody :: ([Declaration] -> [Declaration]) -> TypeInstanceBody -> TypeInstanceBody
- traverseTypeInstanceBody :: Applicative f => ([Declaration] -> f [Declaration]) -> TypeInstanceBody -> f TypeInstanceBody
- isValueDecl :: Declaration -> Bool
- isDataDecl :: Declaration -> Bool
- isImportDecl :: Declaration -> Bool
- isExternDataDecl :: Declaration -> Bool
- isFixityDecl :: Declaration -> Bool
- isExternDecl :: Declaration -> Bool
- isTypeClassInstanceDeclaration :: Declaration -> Bool
- isTypeClassDeclaration :: Declaration -> Bool
- flattenDecls :: [Declaration] -> [Declaration]
- type Guard = Expr
- data Expr
- = Literal (Literal Expr)
- | UnaryMinus Expr
- | BinaryNoParens Expr Expr Expr
- | Parens Expr
- | OperatorSection Expr (Either Expr Expr)
- | ObjectGetter String
- | Accessor String Expr
- | ObjectUpdate Expr [(String, Expr)]
- | Abs (Either Ident Binder) Expr
- | App Expr Expr
- | Var (Qualified Ident)
- | IfThenElse Expr Expr Expr
- | Constructor (Qualified (ProperName ConstructorName))
- | Case [Expr] [CaseAlternative]
- | TypedValue Bool Expr Type
- | Let [Declaration] Expr
- | Do [DoNotationElement]
- | TypeClassDictionaryConstructorApp (Qualified (ProperName ClassName)) Expr
- | TypeClassDictionary Constraint (Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) TypeClassDictionaryInScope)))
- | TypeClassDictionaryAccessor (Qualified (ProperName ClassName)) Ident
- | SuperClassDictionary (Qualified (ProperName ClassName)) [Type]
- | AnonymousArgument
- | PositionedValue SourceSpan [Comment] Expr
- data CaseAlternative = CaseAlternative {
- caseAlternativeBinders :: [Binder]
- caseAlternativeResult :: Either [(Guard, Expr)] Expr
- data DoNotationElement
Documentation
A module declaration, consisting of comments about the module, a module name, a list of declarations, and a list of the declarations that are explicitly exported. If the export list is Nothing, everything is exported.
getModuleName :: Module -> ModuleName Source
Return a module's name.
addDefaultImport :: ModuleName -> Module -> Module Source
Add an import declaration for a module if it does not already explicitly import it.
data DeclarationRef Source
An item in a list of explicit imports or exports
TypeRef (ProperName TypeName) (Maybe [ProperName ConstructorName]) | A type constructor with data constructors |
ValueRef Ident | A value |
TypeClassRef (ProperName ClassName) | A type class |
TypeInstanceRef Ident | A type class instance, created during typeclass desugaring (name, class name, instance types) |
ModuleRef ModuleName | A module, in its entirety |
ProperRef String | An unspecified ProperName ref. This will be replaced with a TypeClassRef or TypeRef during name desugaring. |
PositionedDeclarationRef SourceSpan [Comment] DeclarationRef | A declaration reference with source position information |
isModuleRef :: DeclarationRef -> Bool Source
findDuplicateRefs :: [DeclarationRef] -> ([DeclarationRef], [ProperName ConstructorName]) Source
Finds duplicate values in a list of declaration refs. The returned values are the duplicate refs with data constructors elided, and then a separate list of duplicate data constructors.
data ImportDeclarationType Source
The data type which specifies type of import declaration
Implicit | An import with no explicit list: `import M`. |
Explicit [DeclarationRef] | An import with an explicit list of references to import: `import M (foo)` |
Hiding [DeclarationRef] | An import with a list of references to hide: `import M hiding (foo)` |
data Declaration Source
The data type of declarations
DataDeclaration DataDeclType (ProperName TypeName) [(String, Maybe Kind)] [(ProperName ConstructorName, [Type])] | A data type declaration (data or newtype, name, arguments, data constructors) |
DataBindingGroupDeclaration [Declaration] | A minimal mutually recursive set of data type declarations |
TypeSynonymDeclaration (ProperName TypeName) [(String, Maybe Kind)] Type | A type synonym declaration (name, arguments, type) |
TypeDeclaration Ident Type | A type declaration for a value (name, ty) |
ValueDeclaration Ident NameKind [Binder] (Either [(Guard, Expr)] Expr) | A value declaration (name, top-level binders, optional guard, value) |
BindingGroupDeclaration [(Ident, NameKind, Expr)] | A minimal mutually recursive set of value declarations |
ExternDeclaration Ident Type | A foreign import declaration (name, type) |
ExternDataDeclaration (ProperName TypeName) Kind | A data type foreign import (name, kind) |
FixityDeclaration Fixity String (Maybe (Either (Qualified Ident) (Qualified (ProperName ConstructorName)))) | A fixity declaration (fixity data, operator name, value the operator is an alias for) |
ImportDeclaration ModuleName ImportDeclarationType (Maybe ModuleName) Bool | A module import (module name, qualifiedunqualifiedhiding, optional "qualified as" name)
TODO: also a boolean specifying whether the old |
TypeClassDeclaration (ProperName ClassName) [(String, Maybe Kind)] [Constraint] [Declaration] | A type class declaration (name, argument, implies, member declarations) |
TypeInstanceDeclaration Ident [Constraint] (Qualified (ProperName ClassName)) [Type] TypeInstanceBody | A type instance declaration (name, dependencies, class name, instance types, member declarations) |
PositionedDeclaration SourceSpan [Comment] Declaration | A declaration with source position information |
data TypeInstanceBody Source
The members of a type class instance declaration
DerivedInstance | This is a derived instance |
ExplicitInstance [Declaration] | This is a regular (explicit) instance |
mapTypeInstanceBody :: ([Declaration] -> [Declaration]) -> TypeInstanceBody -> TypeInstanceBody Source
traverseTypeInstanceBody :: Applicative f => ([Declaration] -> f [Declaration]) -> TypeInstanceBody -> f TypeInstanceBody Source
A traversal for TypeInstanceBody
isValueDecl :: Declaration -> Bool Source
Test if a declaration is a value declaration
isDataDecl :: Declaration -> Bool Source
Test if a declaration is a data type or type synonym declaration
isImportDecl :: Declaration -> Bool Source
Test if a declaration is a module import
isExternDataDecl :: Declaration -> Bool Source
Test if a declaration is a data type foreign import
isFixityDecl :: Declaration -> Bool Source
Test if a declaration is a fixity declaration
isExternDecl :: Declaration -> Bool Source
Test if a declaration is a foreign import
isTypeClassInstanceDeclaration :: Declaration -> Bool Source
Test if a declaration is a type class instance declaration
isTypeClassDeclaration :: Declaration -> Bool Source
Test if a declaration is a type class declaration
flattenDecls :: [Declaration] -> [Declaration] Source
Recursively flatten data binding groups in the list of declarations
A guard is just a boolean-valued expression that appears alongside a set of binders
Data type for expressions and terms
Literal (Literal Expr) | A literal value |
UnaryMinus Expr | A prefix -, will be desugared |
BinaryNoParens Expr Expr Expr | Binary operator application. During the rebracketing phase of desugaring, this data constructor will be removed. |
Parens Expr | Explicit parentheses. During the rebracketing phase of desugaring, this data constructor will be removed. Note: although it seems this constructor is not used, it _is_ useful, since it prevents certain traversals from matching. |
OperatorSection Expr (Either Expr Expr) | Operator section. This will be removed during desugaring and replaced with lambda. |
ObjectGetter String | An object property getter (e.g. `_.x`). This will be removed during desugaring and expanded into a lambda that reads a property from an object. |
Accessor String Expr | An record property accessor expression |
ObjectUpdate Expr [(String, Expr)] | Partial record update |
Abs (Either Ident Binder) Expr | Function introduction |
App Expr Expr | Function application |
Var (Qualified Ident) | Variable |
IfThenElse Expr Expr Expr | Conditional (if-then-else expression) |
Constructor (Qualified (ProperName ConstructorName)) | A data constructor |
Case [Expr] [CaseAlternative] | A case expression. During the case expansion phase of desugaring, top-level binders will get desugared into case expressions, hence the need for guards and multiple binders per branch here. |
TypedValue Bool Expr Type | A value with a type annotation |
Let [Declaration] Expr | A let binding |
Do [DoNotationElement] | A do-notation block |
TypeClassDictionaryConstructorApp (Qualified (ProperName ClassName)) Expr | An application of a typeclass dictionary constructor. The value should be an ObjectLiteral. |
TypeClassDictionary Constraint (Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) TypeClassDictionaryInScope))) | A placeholder for a type class dictionary to be inserted later. At the end of type checking, these placeholders will be replaced with actual expressions representing type classes dictionaries which can be evaluated at runtime. The constructor arguments represent (in order): whether or not to look at superclass implementations when searching for a dictionary, the type class name and instance type, and the type class dictionaries in scope. |
TypeClassDictionaryAccessor (Qualified (ProperName ClassName)) Ident | A typeclass dictionary accessor, the implementation is left unspecified until CoreFn desugaring. |
SuperClassDictionary (Qualified (ProperName ClassName)) [Type] | A placeholder for a superclass dictionary to be turned into a TypeClassDictionary during typechecking |
AnonymousArgument | A placeholder for an anonymous function argument |
PositionedValue SourceSpan [Comment] Expr | A value with source position information |
data CaseAlternative Source
An alternative in a case statement
CaseAlternative | |
|
data DoNotationElement Source
A statement in a do-notation block
DoNotationValue Expr | A monadic value without a binder |
DoNotationBind Binder Expr | A monadic value with a binder |
DoNotationLet [Declaration] | A let statement, i.e. a pure value with a binder |
PositionedDoNotationElement SourceSpan [Comment] DoNotationElement | A do notation element with source position information |