Agda-2.5.1.1: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Syntax.Concrete.Definitions

Description

Preprocess Declarations, producing NiceDeclarations.

  • Attach fixity and syntax declarations to the definition they refer to.
  • Distribute the following attributes to the individual definitions: abstract, instance, postulate, primitive, private, termination pragmas.
  • Gather the function clauses belonging to one function definition.
  • Expand ellipsis ... in function clauses following with.
  • Infer mutual blocks. A block starts when a lone signature is encountered, and ends when all lone signatures have seen their definition.
  • Report basic well-formedness error, when one of the above transformation fails.

Synopsis

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

Axiom Range Fixity' Access IsInstance ArgInfo Name Expr

Axioms and functions can be declared irrelevant. (Hiding should be NotHidden)

NiceField Range IsInstance Fixity' Access IsAbstract Name (Arg Expr) 
PrimitiveFunction Range Fixity' Access IsAbstract Name Expr 
NiceMutual Range TerminationCheck PositivityCheck [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 PositivityCheck 
NiceDataSig Range Fixity' Access Name [LamBinding] Expr PositivityCheck 
NiceFunClause Range Access IsAbstract TerminationCheck Catchall Declaration

An uncategorized function clause, could be a function clause without type signature or a pattern lhs (e.g. for irrefutable let). The Declaration is the actual FunClause.

FunSig Range Fixity' Access IsInstance IsMacro ArgInfo TerminationCheck Name Expr 
FunDef Range [Declaration] Fixity' IsAbstract TerminationCheck Name [Clause]

Block of function clauses (we have seen the type signature before). The Declarations are the original declarations that were processed into this FunDef and are only used in notSoNiceDeclaration.

DataDef Range Fixity' IsAbstract Name [LamBinding] PositivityCheck [NiceConstructor] 
RecDef Range Fixity' IsAbstract Name (Maybe (Ranged Induction)) (Maybe Bool) (Maybe (ThingWithFixity Name, IsInstance)) [LamBinding] PositivityCheck [NiceDeclaration] 
NicePatternSyn Range Fixity' Name [Arg Name] Pattern 
NiceUnquoteDecl Range [Fixity'] Access IsInstance IsAbstract TerminationCheck [Name] Expr 
NiceUnquoteDef Range [Fixity'] Access IsAbstract TerminationCheck [Name] Expr 

data Clause Source #

One clause in a function definition. There is no guarantee that the LHS actually declares the Name. We will have to check that later.

Constructors

Clause Name Catchall LHS RHS WhereClause [Clause] 

type Nice = StateT NiceEnv (Either DeclarationException) Source #

Nicifier monad.

type Measure = Name Source #

Termination measure is, for now, a variable name.