Agda-2.6.1.1: A dependently typed functional programming language and proof assistant
Safe HaskellNone
LanguageHaskell2010

Agda.TypeChecking.Rules.Decl

Contents

Synopsis

Documentation

checkDeclCached :: Declaration -> TCM () Source #

Cached checkDecl

checkDecls :: [Declaration] -> TCM () Source #

Type check a sequence of declarations.

checkDecl :: Declaration -> TCM () Source #

Type check a single declaration.

revisitRecordPatternTranslation :: [QName] -> TCM () Source #

Check if there is a inferred eta record type in the mutual block. If yes, repeat the record pattern translation for all function definitions in the block. This is necessary since the original record pattern translation will have skipped record patterns of the new record types (as eta was off for them). See issue 2197).

unquoteTop :: [QName] -> Expr -> TCM [QName] Source #

Run a reflected TCM computatation expected to define a given list of names.

instantiateDefinitionType :: QName -> TCM () Source #

Instantiate all metas in Definition associated to QName. Makes sense after freezing metas. Some checks, like free variable analysis, are not in TCM, so they will be more precise (see issue 1099) after meta instantiation. Precondition: name has been added to signature already.

highlight_ :: HighlightModuleContents -> Declaration -> TCM () Source #

Highlight a declaration. Called after checking a mutual block (to ensure we have the right definitions for all names). For modules inside mutual blocks we haven't highlighted their contents, but for modules not in a mutual block we have. Hence the flag.

checkTermination_ :: Declaration -> TCM () Source #

Termination check a declaration.

checkPositivity_ :: MutualInfo -> Set QName -> TCM () Source #

Check a set of mutual names for positivity.

checkCoinductiveRecords :: [Declaration] -> TCM () Source #

Check that all coinductive records are actually recursive. (Otherwise, one can implement invalid recursion schemes just like for the old coinduction.)

checkInjectivity_ :: Set QName -> TCM () Source #

Check a set of mutual names for constructor-headedness.

checkProjectionLikeness_ :: Set QName -> TCM () Source #

Check a set of mutual names for projection likeness.

Only a single, non-abstract function can be projection-like. Making an abstract function projection-like would break the invariant that the type of the principle argument of a projection-like function is always inferable.

whenAbstractFreezeMetasAfter :: DefInfo -> TCM a -> TCM a Source #

Freeze metas created by given computation if in abstract mode.

checkAxiom :: Axiom -> DefInfo -> ArgInfo -> Maybe [Occurrence] -> QName -> Expr -> TCM () Source #

Type check an axiom.

checkAxiom' :: Maybe GeneralizeTelescope -> Axiom -> DefInfo -> ArgInfo -> Maybe [Occurrence] -> QName -> Expr -> TCM () Source #

Data and record type signatures need to remember the generalized parameters for when checking the corresponding definition, so for these we pass in the parameter telescope separately.

checkPrimitive :: DefInfo -> QName -> Expr -> TCM () Source #

Type check a primitive function declaration.

checkPragma :: Range -> Pragma -> TCM () Source #

Check a pragma.

checkMutual :: MutualInfo -> [Declaration] -> TCM (MutualId, Set QName) Source #

Type check a bunch of mutual inductive recursive definitions.

All definitions which have so far been assigned to the given mutual block are returned.

checkTypeSignature :: TypeSignature -> TCM () Source #

Type check the type signature of an inductive or recursive definition.

checkModuleArity Source #

Arguments

:: ModuleName

Name of applied module.

-> Telescope

The module parameters.

-> [NamedArg Expr]

The arguments this module is applied to.

-> TCM Telescope

The remaining module parameters (has free de Bruijn indices!).

Helper for checkSectionApplication.

Matches the arguments of the module application with the module parameters.

Returns the remaining module parameters as an open telescope. Warning: the returned telescope is not the final result, an actual instantiation of the parameters does not occur.

checkSectionApplication Source #

Arguments

:: ModuleInfo 
-> ModuleName

Name m1 of module defined by the module macro.

-> ModuleApplication

The module macro λ tel → m2 args.

-> ScopeCopyInfo

Imported names and modules

-> TCM () 

Check an application of a section (top-level function, includes traceCall).

checkSectionApplication' Source #

Arguments

:: ModuleInfo 
-> ModuleName

Name m1 of module defined by the module macro.

-> ModuleApplication

The module macro λ tel → m2 args.

-> ScopeCopyInfo

Imported names and modules

-> TCM () 

Check an application of a section.

checkImport :: ModuleInfo -> ModuleName -> TCM () Source #

Type check an import declaration. Actually doesn't do anything, since all the work is done when scope checking.

Debugging

class ShowHead a where Source #

Methods

showHead :: a -> String Source #

Instances

Instances details
ShowHead Declaration Source # 
Instance details

Defined in Agda.TypeChecking.Rules.Decl