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

Safe HaskellNone
LanguageHaskell98

Agda.TypeChecking.Monad.Signature

Synopsis

Documentation

addConstant :: QName -> Definition -> TCM () Source

Add a constant to the signature. Lifts the definition to top level.

setTerminates :: QName -> Bool -> TCM () Source

Set termination info of a defined function symbol.

modifyFunClauses :: QName -> ([Clause] -> [Clause]) -> TCM () Source

Modify the clauses of a function.

addClauses :: QName -> [Clause] -> TCM () Source

Lifts clauses to the top-level and adds them to definition.

addSection :: ModuleName -> TCM () Source

Add a section to the signature.

The current context will be stored as the cumulative module parameters for this section.

lookupSection :: (Functor m, ReadTCState m) => ModuleName -> m Telescope Source

Lookup a section. If it doesn't exist that just means that the module wasn't parameterised.

applySection Source

Arguments

:: ModuleName

Name of new module defined by the module macro.

-> Telescope

Parameters of new module.

-> ModuleName

Name of old module applied to arguments.

-> Args

Arguments of module application.

-> Ren QName

Imported names (given as renaming).

-> Ren ModuleName

Imported modules (given as renaming).

-> TCM () 

Module application (followed by module parameter abstraction).

addDisplayForm :: QName -> DisplayForm -> TCM () Source

Add a display form to a definition (could be in this or imported signature).

chaseDisplayForms :: QName -> TCM (Set QName) Source

Find all names used (recursively) by display forms of a given name.

hasLoopingDisplayForm :: QName -> TCM Bool Source

Check if a display form is looping.

whatInduction :: QName -> TCM Induction Source

Can be called on either a (co)datatype, a record type or a (co)constructor.

singleConstructorType :: QName -> TCM Bool Source

Does the given constructor come from a single-constructor type?

Precondition: The name has to refer to a constructor.

class (Functor m, Applicative m, Monad m) => HasConstInfo m where Source

Methods

getConstInfo :: QName -> m Definition Source

Lookup the definition of a name. The result is a closed thing, all free variables have been abstracted over.

getRewriteRulesFor :: QName -> m RewriteRules Source

Lookup the rewrite rules with the given head symbol.

getPolarity :: QName -> TCM [Polarity] Source

Look up the polarity of a definition.

getPolarity' :: Comparison -> QName -> TCM [Polarity] Source

Look up polarity of a definition and compose with polarity represented by Comparison.

setPolarity :: QName -> [Polarity] -> TCM () Source

Set the polarity of a definition.

getArgOccurrence :: QName -> Nat -> TCM Occurrence Source

Get argument occurrence info for argument i of definition d (never fails).

getMutual :: QName -> TCM [QName] Source

Get the mutually recursive identifiers.

setMutual :: QName -> [QName] -> TCM () Source

Set the mutually recursive identifiers.

mutuallyRecursive :: QName -> QName -> TCM Bool Source

Check whether two definitions are mutually recursive.

getSection :: ModuleName -> TCM (Maybe Section) Source

Why Maybe? The reason is that we look up all prefixes of a module to compute number of parameters, and for hierarchical top-level modules, A.B.C say, A and A.B do not exist.

getCurrentModuleFreeVars :: TCM Nat Source

Get the number of parameters to the current module.

getDefFreeVars :: (Functor m, Applicative m, ReadTCState m, MonadReader TCEnv m) => QName -> m Nat Source

Compute the number of free variables of a defined name. This is the sum of number of parameters shared with the current module and the number of anonymous variables (if the name comes from a let-bound module).

freeVarsToApply :: QName -> TCM Args Source

Compute the context variables to apply a definition to.

We have to insert the module telescope of the common prefix of the current module and the module where the definition comes from. (Properly raised to the current context.)

Example: module M₁ Γ where module M₁ Δ where f = ... module M₃ Θ where ... M₁.M₂.f [insert Γ raised by Θ]

inFreshModuleIfFreeParams :: TCM a -> TCM a Source

Unless all variables in the context are module parameters, create a fresh module to capture the non-module parameters. Used when unquoting to make sure generated definitions work properly.

instantiateDef :: Definition -> TCM Definition Source

Instantiate a closed definition with the correct part of the current context.

makeAbstract :: Definition -> Maybe Definition Source

Give the abstract view of a definition.

inAbstractMode :: TCM a -> TCM a Source

Enter abstract mode. Abstract definition in the current module are transparent.

inConcreteMode :: TCM a -> TCM a Source

Not in abstract mode. All abstract definitions are opaque.

ignoreAbstractMode :: MonadReader TCEnv m => m a -> m a Source

Ignore abstract mode. All abstract definitions are transparent.

inConcreteOrAbstractMode :: QName -> TCM a -> TCM a Source

Enter concrete or abstract mode depending on whether the given identifier is concrete or abstract.

treatAbstractly :: MonadReader TCEnv m => QName -> m Bool Source

Check whether a name might have to be treated abstractly (either if we're inAbstractMode or it's not a local name). Returns true for things not declared abstract as well, but for those makeAbstract will have no effect.

treatAbstractly' :: QName -> TCEnv -> Bool Source

Andreas, 2015-07-01: If the current module is a weak suffix of the identifier module, we can see through its abstract definition if we are abstract. (Then treatAbstractly' returns False).

If I am not mistaken, then we cannot see definitions in the where block of an abstract function from the perspective of the function, because then the current module is a strict prefix of the module of the local identifier. This problem is fixed by removing trailing anonymous module name parts (underscores) from both names.

typeOfConst :: QName -> TCM Type Source

Get type of a constant, instantiated to the current context.

relOfConst :: QName -> TCM Relevance Source

Get relevance of a constant.

sortOfConst :: QName -> TCM Sort Source

The name must be a datatype.

defPars :: Definition -> Int Source

The number of parameters of a definition.

droppedPars :: Definition -> Int Source

The number of dropped parameters for a definition. 0 except for projection(-like) functions and constructors.

isProjection :: HasConstInfo m => QName -> m (Maybe Projection) Source

Is it the name of a record projection?

isStaticFun :: Defn -> Bool Source

Is it a function marked STATIC?

isInlineFun :: Defn -> Bool Source

Is it a function marked INLINE?

isProperProjection :: Defn -> Bool Source

Returns True if we are dealing with a proper projection, i.e., not a projection-like function nor a record field value (projection applied to argument).

projectionArgs :: Defn -> Int Source

Number of dropped initial arguments of a projection(-like) function.

usesCopatterns :: QName -> TCM Bool Source

Check whether a definition uses copatterns.

applyDef :: QName -> Arg Term -> TCM Term Source

Apply a function f to its first argument, producing the proper postfix projection if f is a projection.