| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Axel.AST
Documentation
class ToHaskell a where Source #
Minimal complete definition
Instances
type Identifier = String Source #
Constructors
| CaseBlock | |
Fields
| |
data FunctionApplication Source #
Constructors
| FunctionApplication | |
Fields
| |
Instances
| Eq FunctionApplication Source # | |
Defined in Axel.AST Methods (==) :: FunctionApplication -> FunctionApplication -> Bool # (/=) :: FunctionApplication -> FunctionApplication -> Bool # | |
| Show FunctionApplication Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> FunctionApplication -> ShowS # show :: FunctionApplication -> String # showList :: [FunctionApplication] -> ShowS # | |
| ToHaskell FunctionApplication Source # | |
| HasFunction FunctionApplication Expression Source # | |
Defined in Axel.AST Methods | |
| HasConstructors DataDeclaration [FunctionApplication] Source # | |
Defined in Axel.AST Methods constructors :: Lens' DataDeclaration [FunctionApplication] Source # | |
| HasArguments FunctionApplication [Expression] Source # | |
Defined in Axel.AST Methods arguments :: Lens' FunctionApplication [Expression] Source # | |
Constructors
| TopLevel | |
Fields
| |
data TypeDefinition Source #
Constructors
| ProperType Identifier | |
| TypeConstructor FunctionApplication |
Instances
| Eq TypeDefinition Source # | |
Defined in Axel.AST Methods (==) :: TypeDefinition -> TypeDefinition -> Bool # (/=) :: TypeDefinition -> TypeDefinition -> Bool # | |
| Show TypeDefinition Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> TypeDefinition -> ShowS # show :: TypeDefinition -> String # showList :: [TypeDefinition] -> ShowS # | |
| ToHaskell TypeDefinition Source # | |
| HasTypeDefinition DataDeclaration TypeDefinition Source # | |
Defined in Axel.AST Methods typeDefinition :: Lens' DataDeclaration TypeDefinition Source # | |
data DataDeclaration Source #
Constructors
| DataDeclaration | |
Fields | |
Instances
| Eq DataDeclaration Source # | |
Defined in Axel.AST Methods (==) :: DataDeclaration -> DataDeclaration -> Bool # (/=) :: DataDeclaration -> DataDeclaration -> Bool # | |
| Show DataDeclaration Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> DataDeclaration -> ShowS # show :: DataDeclaration -> String # showList :: [DataDeclaration] -> ShowS # | |
| ToHaskell DataDeclaration Source # | |
| HasTypeDefinition DataDeclaration TypeDefinition Source # | |
Defined in Axel.AST Methods typeDefinition :: Lens' DataDeclaration TypeDefinition Source # | |
| HasConstructors DataDeclaration [FunctionApplication] Source # | |
Defined in Axel.AST Methods constructors :: Lens' DataDeclaration [FunctionApplication] Source # | |
data FunctionDefinition Source #
Constructors
| FunctionDefinition | |
Fields
| |
Instances
| Eq FunctionDefinition Source # | |
Defined in Axel.AST Methods (==) :: FunctionDefinition -> FunctionDefinition -> Bool # (/=) :: FunctionDefinition -> FunctionDefinition -> Bool # | |
| Show FunctionDefinition Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> FunctionDefinition -> ShowS # show :: FunctionDefinition -> String # showList :: [FunctionDefinition] -> ShowS # | |
| ToHaskell FunctionDefinition Source # | |
| HasName FunctionDefinition Identifier Source # | |
Defined in Axel.AST Methods | |
| HasBody FunctionDefinition Expression Source # | |
Defined in Axel.AST Methods | |
| HasFunctionDefinition MacroDefinition FunctionDefinition Source # | |
Defined in Axel.AST | |
| HasArguments FunctionDefinition [Expression] Source # | |
Defined in Axel.AST Methods | |
| HasDefinitions TypeclassInstance [FunctionDefinition] Source # | |
Defined in Axel.AST Methods definitions :: Lens' TypeclassInstance [FunctionDefinition] Source # | |
Constructors
| ImportItem Identifier | |
| ImportType Identifier [Identifier] |
data ImportSpecification Source #
Constructors
| ImportAll | |
| ImportOnly [Import] |
Instances
| Eq ImportSpecification Source # | |
Defined in Axel.AST Methods (==) :: ImportSpecification -> ImportSpecification -> Bool # (/=) :: ImportSpecification -> ImportSpecification -> Bool # | |
| Show ImportSpecification Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> ImportSpecification -> ShowS # show :: ImportSpecification -> String # showList :: [ImportSpecification] -> ShowS # | |
| ToHaskell ImportSpecification Source # | |
| HasImports RestrictedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' RestrictedImport ImportSpecification Source # | |
| HasImports QualifiedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' QualifiedImport ImportSpecification Source # | |
Constructors
| Lambda | |
Fields
| |
Constructors
| LetBlock | |
Fields
| |
newtype MacroDefinition Source #
Constructors
| MacroDefinition | |
Fields | |
Instances
| Eq MacroDefinition Source # | |
Defined in Axel.AST Methods (==) :: MacroDefinition -> MacroDefinition -> Bool # (/=) :: MacroDefinition -> MacroDefinition -> Bool # | |
| Show MacroDefinition Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> MacroDefinition -> ShowS # show :: MacroDefinition -> String # showList :: [MacroDefinition] -> ShowS # | |
| ToHaskell MacroDefinition Source # | |
| HasFunctionDefinition MacroDefinition FunctionDefinition Source # | |
Defined in Axel.AST | |
Constructors
| Pragma | |
Fields | |
data QualifiedImport Source #
Constructors
| QualifiedImport | |
Fields | |
Instances
| Eq QualifiedImport Source # | |
Defined in Axel.AST Methods (==) :: QualifiedImport -> QualifiedImport -> Bool # (/=) :: QualifiedImport -> QualifiedImport -> Bool # | |
| Show QualifiedImport Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> QualifiedImport -> ShowS # show :: QualifiedImport -> String # showList :: [QualifiedImport] -> ShowS # | |
| ToHaskell QualifiedImport Source # | |
| HasModuleName QualifiedImport Identifier Source # | |
Defined in Axel.AST Methods | |
| HasImports QualifiedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' QualifiedImport ImportSpecification Source # | |
| HasAlias QualifiedImport Identifier Source # | |
Defined in Axel.AST Methods | |
data RestrictedImport Source #
Constructors
| RestrictedImport | |
Fields | |
Instances
| Eq RestrictedImport Source # | |
Defined in Axel.AST Methods (==) :: RestrictedImport -> RestrictedImport -> Bool # (/=) :: RestrictedImport -> RestrictedImport -> Bool # | |
| Show RestrictedImport Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> RestrictedImport -> ShowS # show :: RestrictedImport -> String # showList :: [RestrictedImport] -> ShowS # | |
| ToHaskell RestrictedImport Source # | |
| HasModuleName RestrictedImport Identifier Source # | |
Defined in Axel.AST Methods | |
| HasImports RestrictedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' RestrictedImport ImportSpecification Source # | |
data TypeclassInstance Source #
Constructors
| TypeclassInstance | |
Fields | |
Instances
| Eq TypeclassInstance Source # | |
Defined in Axel.AST Methods (==) :: TypeclassInstance -> TypeclassInstance -> Bool # (/=) :: TypeclassInstance -> TypeclassInstance -> Bool # | |
| Show TypeclassInstance Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> TypeclassInstance -> ShowS # show :: TypeclassInstance -> String # showList :: [TypeclassInstance] -> ShowS # | |
| ToHaskell TypeclassInstance Source # | |
| HasInstanceName TypeclassInstance Expression Source # | |
Defined in Axel.AST Methods | |
| HasDefinitions TypeclassInstance [FunctionDefinition] Source # | |
Defined in Axel.AST Methods definitions :: Lens' TypeclassInstance [FunctionDefinition] Source # | |
data TypeSignature Source #
Constructors
| TypeSignature | |
Fields | |
Instances
| Eq TypeSignature Source # | |
Defined in Axel.AST Methods (==) :: TypeSignature -> TypeSignature -> Bool # (/=) :: TypeSignature -> TypeSignature -> Bool # | |
| Show TypeSignature Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> TypeSignature -> ShowS # show :: TypeSignature -> String # showList :: [TypeSignature] -> ShowS # | |
| ToHaskell TypeSignature Source # | |
| HasTypeDefinition TypeSignature Expression Source # | |
Defined in Axel.AST Methods | |
| HasName TypeSignature Identifier Source # | |
Defined in Axel.AST Methods | |
data TypeSynonym Source #
Constructors
| TypeSynonym | |
Fields | |
Instances
| Eq TypeSynonym Source # | |
Defined in Axel.AST | |
| Show TypeSynonym Source # | |
Defined in Axel.AST Methods showsPrec :: Int -> TypeSynonym -> ShowS # show :: TypeSynonym -> String # showList :: [TypeSynonym] -> ShowS # | |
| ToHaskell TypeSynonym Source # | |
| HasAlias TypeSynonym Expression Source # | |
Defined in Axel.AST Methods | |
| HasDefinition TypeSynonym Expression Source # | |
Defined in Axel.AST Methods | |
data Expression Source #
Constructors
| ECaseBlock CaseBlock | |
| EEmptySExpression | |
| EFunctionApplication FunctionApplication | |
| EIdentifier Identifier | |
| ELambda Lambda | |
| ELetBlock LetBlock | |
| ELiteral Literal |
Instances
Constructors
class HasMatches s a | s -> a where Source #
Minimal complete definition
Instances
| HasMatches CaseBlock [(Expression, Expression)] Source # | |
Defined in Axel.AST Methods matches :: Lens' CaseBlock [(Expression, Expression)] Source # | |
class HasConstructors s a | s -> a where Source #
Minimal complete definition
Methods
constructors :: Lens' s a Source #
Instances
| HasConstructors DataDeclaration [FunctionApplication] Source # | |
Defined in Axel.AST Methods constructors :: Lens' DataDeclaration [FunctionApplication] Source # | |
class HasTypeDefinition s a | s -> a where Source #
Minimal complete definition
Methods
typeDefinition :: Lens' s a Source #
Instances
| HasTypeDefinition TypeSignature Expression Source # | |
Defined in Axel.AST Methods | |
| HasTypeDefinition DataDeclaration TypeDefinition Source # | |
Defined in Axel.AST Methods typeDefinition :: Lens' DataDeclaration TypeDefinition Source # | |
class HasArguments s a | s -> a where Source #
Minimal complete definition
Instances
| HasArguments Lambda [Expression] Source # | |
| HasArguments FunctionDefinition [Expression] Source # | |
Defined in Axel.AST Methods | |
| HasArguments FunctionApplication [Expression] Source # | |
Defined in Axel.AST Methods arguments :: Lens' FunctionApplication [Expression] Source # | |
class HasFunction s a | s -> a where Source #
Minimal complete definition
Instances
| HasFunction FunctionApplication Expression Source # | |
Defined in Axel.AST Methods | |
class HasBody s a | s -> a where Source #
Minimal complete definition
Instances
| HasBody LetBlock Expression Source # | |
| HasBody Lambda Expression Source # | |
| HasBody FunctionDefinition Expression Source # | |
Defined in Axel.AST Methods | |
class HasName s a | s -> a where Source #
Minimal complete definition
Instances
| HasName TypeSignature Identifier Source # | |
Defined in Axel.AST Methods | |
| HasName FunctionDefinition Identifier Source # | |
Defined in Axel.AST Methods | |
class HasBindings s a | s -> a where Source #
Minimal complete definition
Instances
| HasBindings LetBlock [(Expression, Expression)] Source # | |
Defined in Axel.AST Methods bindings :: Lens' LetBlock [(Expression, Expression)] Source # | |
class HasFunctionDefinition s a | s -> a where Source #
Minimal complete definition
Methods
functionDefinition :: Lens' s a Source #
Instances
| HasFunctionDefinition MacroDefinition FunctionDefinition Source # | |
Defined in Axel.AST | |
class HasPragmaSpecification s a | s -> a where Source #
Minimal complete definition
Methods
pragmaSpecification :: Lens' s a Source #
class HasAlias s a | s -> a where Source #
Minimal complete definition
Instances
| HasAlias TypeSynonym Expression Source # | |
Defined in Axel.AST Methods | |
| HasAlias QualifiedImport Identifier Source # | |
Defined in Axel.AST Methods | |
class HasImports s a | s -> a where Source #
Minimal complete definition
Instances
| HasImports RestrictedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' RestrictedImport ImportSpecification Source # | |
| HasImports QualifiedImport ImportSpecification Source # | |
Defined in Axel.AST Methods imports :: Lens' QualifiedImport ImportSpecification Source # | |
class HasModuleName s a | s -> a where Source #
Minimal complete definition
Methods
moduleName :: Lens' s a Source #
Instances
| HasModuleName RestrictedImport Identifier Source # | |
Defined in Axel.AST Methods | |
| HasModuleName QualifiedImport Identifier Source # | |
Defined in Axel.AST Methods | |
class HasStatements s a | s -> a where Source #
Minimal complete definition
Methods
statements :: Lens' s a Source #
class HasDefinitions s a | s -> a where Source #
Minimal complete definition
Methods
definitions :: Lens' s a Source #
Instances
| HasDefinitions TypeclassInstance [FunctionDefinition] Source # | |
Defined in Axel.AST Methods definitions :: Lens' TypeclassInstance [FunctionDefinition] Source # | |
class HasInstanceName s a | s -> a where Source #
Minimal complete definition
Methods
instanceName :: Lens' s a Source #
Instances
| HasInstanceName TypeclassInstance Expression Source # | |
Defined in Axel.AST Methods | |
class HasDefinition s a | s -> a where Source #
Minimal complete definition
Methods
definition :: Lens' s a Source #
Instances
| HasDefinition TypeSynonym Expression Source # | |
Defined in Axel.AST Methods | |