| Safe Haskell | None |
|---|
Agda.Syntax.Concrete.Definitions
- data NiceDeclaration
- = Axiom Range Fixity' Access IsInstance ArgInfo Name Expr
- | NiceField Range Fixity' Access IsAbstract Name (Arg Expr)
- | PrimitiveFunction Range Fixity' Access IsAbstract Name Expr
- | NiceMutual Range TerminationCheck [NiceDeclaration]
- | NiceModule Range Access IsAbstract QName Telescope [Declaration]
- | NiceModuleMacro Range Access Name ModuleApplication OpenShortHand ImportDirective
- | NiceOpen Range QName ImportDirective
- | NiceImport Range QName (Maybe AsName) OpenShortHand ImportDirective
- | NicePragma Range Pragma
- | NiceRecSig Range Fixity' Access Name [LamBinding] Expr
- | NiceDataSig Range Fixity' Access Name [LamBinding] Expr
- | NiceFunClause Range Access IsAbstract TerminationCheck Declaration
- | FunSig Range Fixity' Access IsInstance ArgInfo TerminationCheck Name Expr
- | FunDef Range [Declaration] Fixity' IsAbstract TerminationCheck Name [Clause]
- | DataDef Range Fixity' IsAbstract Name [LamBinding] [NiceConstructor]
- | RecDef Range Fixity' IsAbstract Name (Maybe (Ranged Induction)) (Maybe (ThingWithFixity Name)) [LamBinding] [NiceDeclaration]
- | NicePatternSyn Range Fixity' Name [Arg Name] Pattern
- | NiceUnquoteDecl Range Fixity' Access IsAbstract TerminationCheck Name Expr
- type NiceConstructor = NiceTypeSignature
- type NiceTypeSignature = NiceDeclaration
- data Clause = Clause Name LHS RHS WhereClause [Clause]
- data DeclarationException
- = MultipleFixityDecls [(Name, [Fixity'])]
- | MissingDefinition Name
- | MissingWithClauses Name
- | MissingTypeSignature LHS
- | MissingDataSignature Name
- | WrongDefinition Name DataRecOrFun DataRecOrFun
- | WrongParameters Name
- | NotAllowedInMutual NiceDeclaration
- | UnknownNamesInFixityDecl [Name]
- | Codata Range
- | DeclarationPanic String
- | UselessPrivate Range
- | UselessAbstract Range
- | UselessInstance Range
- | WrongContentPostulateBlock Range
- | AmbiguousFunClauses LHS [Name]
- | InvalidTerminationCheckPragma Range
- | InvalidMeasureMutual Range
- type Nice = StateT NiceEnv (Either DeclarationException)
- runNice :: Nice a -> Either DeclarationException a
- niceDeclarations :: [Declaration] -> Nice [NiceDeclaration]
- notSoNiceDeclaration :: NiceDeclaration -> Declaration
- type Measure = Name
Documentation
data NiceDeclaration Source
The nice declarations. No fixity declarations and function definitions are
contained in a single constructor instead of spread out between type
signatures and clauses. The private, postulate, abstract and instance
modifiers have been distributed to the individual declarations.
Constructors
Instances
type NiceConstructor = NiceTypeSignatureSource
Only Axioms.
type NiceTypeSignature = NiceDeclarationSource
Only Axioms.
One clause in a function definition. There is no guarantee that the LHS
actually declares the Name. We will have to check that later.
Instances
| Show Clause | |
| Typeable Clause | |
| ToAbstract Clause Clause |
data DeclarationException Source
The exception type.
Constructors
| MultipleFixityDecls [(Name, [Fixity'])] | |
| MissingDefinition Name | |
| MissingWithClauses Name | |
| MissingTypeSignature LHS | |
| MissingDataSignature Name | |
| WrongDefinition Name DataRecOrFun DataRecOrFun | |
| WrongParameters Name | |
| NotAllowedInMutual NiceDeclaration | |
| UnknownNamesInFixityDecl [Name] | |
| Codata Range | |
| DeclarationPanic String | |
| UselessPrivate Range | |
| UselessAbstract Range | |
| UselessInstance Range | |
| WrongContentPostulateBlock Range | |
| AmbiguousFunClauses LHS [Name] | in a mutual block, a clause could belong to any of the |
| InvalidTerminationCheckPragma Range | |
| InvalidMeasureMutual Range | In a mutual block, all or none need a MEASURE pragma. Range is of mutual block. |
Instances
type Nice = StateT NiceEnv (Either DeclarationException)Source
runNice :: Nice a -> Either DeclarationException aSource
niceDeclarations :: [Declaration] -> Nice [NiceDeclaration]Source