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

Safe HaskellSafe
LanguageHaskell2010

Agda.Auto.Syntax

Synopsis

Documentation

type UId o = Metavar (Exp o) (RefInfo o) Source #

Unique identifiers for variable occurrences in unification.

data HintMode Source #

Constructors

HMNormal 
HMRecCall 

data RefInfo o Source #

The concrete instance of the blk parameter in Metavar. I.e., the information passed to the search control.

Constructors

RIEnv 

Fields

RIMainInfo 

Fields

  • riMainCxtLength :: Nat

    Size of typing context in which meta was created.

  • riMainType :: HNExp o

    Head normal form of type of meta.

  • riMainIota :: Bool

    True if iota steps performed when normalising target type (used to put cost when traversing a definition by construction instantiation).

RIUnifInfo [CAction o] (HNExp o) 
RICopyInfo (ICExp o) 
RIIotaStep Bool 
RIInferredTypeUnknown 
RINotConstructor 
RIUsedVars [UId o] [Elr o] 
RIPickSubsvar 
RIEqRState EqReasoningState 
RICheckElim Bool 
RICheckProjIndex [ConstRef o] 

type MyPB o = PB (RefInfo o) Source #

type MyMB a o = MB a (RefInfo o) Source #

type Nat = Int Source #

data FMode Source #

Hiding in Agda.

Constructors

Hidden 
Instance 
NotHidden 

Instances

Eq FMode Source # 

Methods

(==) :: FMode -> FMode -> Bool #

(/=) :: FMode -> FMode -> Bool #

data MId Source #

Constructors

Id String 
NoId 

data Abs a Source #

Abstraction with maybe a name.

Different from Agda, where there is also info whether function is constant.

Constructors

Abs MId a 

data ConstDef o Source #

Constant signatures.

Constructors

ConstDef 

Fields

data DeclCont o Source #

Constant definitions.

type Clause o = ([Pat o], MExp o) Source #

data Pat o Source #

Constructors

PatConApp (ConstRef o) [Pat o] 
PatVar String 
PatExp

Dot pattern.

data Elr o Source #

Head of application (elimination).

Constructors

Var Nat 
Const (ConstRef o) 

data Sort Source #

Constructors

Set Nat 
UnknownSort 
Type 

data Exp o Source #

Agsy's internal syntax.

Constructors

App 

Fields

Lam FMode (Abs (MExp o))

Lambda with hiding information.

Pi (Maybe (UId o)) FMode Bool (MExp o) (Abs (MExp o))

True if possibly dependent (var not known to not occur). False if non-dependent.

Sort Sort 
AbsurdLambda FMode

Absurd lambda with hiding information.

type MExp o = MM (Exp o) (RefInfo o) Source #

"Maybe expression": Expression or reference to meta variable.

data ArgList o Source #

Constructors

ALNil

No more eliminations.

ALCons FMode (MExp o) (MArgList o)

Application and tail.

ALProj (MArgList o) (MM (ConstRef o) (RefInfo o)) FMode (MArgList o)

proj pre args, projfcn idx, tail

ALConPar (MArgList o)

Constructor parameter (missing in Agda). Agsy has monomorphic constructors. Inserted to cover glitch of polymorphic constructor applications coming from Agda

type MArgList o = MM (ArgList o) (RefInfo o) Source #

data HNExp o Source #

Constructors

HNApp [Maybe (UId o)] (Elr o) (ICArgList o) 
HNLam [Maybe (UId o)] FMode (Abs (ICExp o)) 
HNPi [Maybe (UId o)] FMode Bool (ICExp o) (Abs (ICExp o)) 
HNSort Sort 

data HNArgList o Source #

Head-normal form of ICArgList. First entry is exposed.

Q: Why are there no projection eliminations?

data ICArgList o Source #

Lazy concatenation of argument lists under explicit substitutions.

Constructors

CALNil 
CALConcat (Clos (MArgList o) o) (ICArgList o) 

type ICExp o = Clos (MExp o) o Source #

An expression a in an explicit substitution [CAction a].

data Clos a o Source #

Constructors

Clos [CAction o] a 

type CExp o = TrBr (ICExp o) o Source #

data TrBr a o Source #

Constructors

TrBr [MExp o] a 

data CAction o Source #

Entry of an explicit substitution.

An explicit substitution is a list of CActions. This is isomorphic to the usual presentation where Skip and Weak would be constructors of exp. substs.

Constructors

Sub (ICExp o)

Instantation of variable.

Skip

For going under a binder, often called Lift.

Weak Nat

Shifting substitution (going to a larger context).

type Ctx o = [(MId, CExp o)] Source #

type EE = IO Source #

sub :: MExp o -> CExp o -> CExp o Source #

subi :: MExp o -> ICExp o -> ICExp o Source #

weak :: Nat -> CExp o -> CExp o Source #

weaki :: Nat -> Clos a o -> Clos a o Source #

weakelr :: Nat -> Elr o -> Elr o Source #

doclos :: [CAction o] -> Nat -> Either Nat (ICExp o) Source #

Substituting for a variable.