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

Safe HaskellNone
LanguageHaskell98

Agda.Termination.Monad

Contents

Description

The monad for the termination checker.

The termination monad TerM is an extension of the type checking monad TCM by an environment with information needed by the termination checker.

Synopsis

Documentation

type MutualNames = [QName] Source

The mutual block we are checking.

The functions are numbered according to their order of appearance in this list.

type Target = QName Source

The target of the function we are checking.

type Guarded = Order Source

The current guardedness level.

data TerEnv Source

The termination environment.

Constructors

TerEnv 

Fields

terUseDotPatterns :: Bool

Are we mining dot patterns to find evindence of structal descent?

terGuardingTypeConstructors :: Bool

Do we assume that record and data type constructors preserve guardedness?

terInlineWithFunctions :: Bool

Do we inline with functions to enhance termination checking of with?

terSizeSuc :: Maybe QName

The name of size successor, if any.

terSharp :: Maybe QName

The name of the delay constructor (sharp), if any.

terCutOff :: CutOff

Depth at which to cut off the structural order.

terCurrent :: QName

The name of the function we are currently checking.

terMutual :: MutualNames

The names of the functions in the mutual block we are checking. This includes the internally generated functions (with, extendedlambda, coinduction).

terUserNames :: [QName]

The list of name actually appearing in the file (abstract syntax). Excludes the internally generated functions.

terTarget :: Maybe Target

Target type of the function we are currently termination checking. Only the constructors of Target are considered guarding.

terDelayed :: Delayed

Are we checking a delayed definition?

terMaskArgs :: [Bool]

Only consider the notMasked False arguments for establishing termination.

terMaskResult :: Bool

Only consider guardedness if False (not masked).

_terSizeDepth :: Int

How many SIZELT relations do we have in the context (= clause telescope). Used to approximate termination for metas in call args.

terPatterns :: MaskedDeBruijnPats

The patterns of the clause we are checking.

terPatternsRaise :: !Int

Number of additional binders we have gone under (and consequently need to raise the patterns to compare to terms). Updated during call graph extraction, hence strict.

terGuarded :: !Guarded

The current guardedness status. Changes as we go deeper into the term. Updated during call graph extraction, hence strict.

terUseSizeLt :: Bool

When extracting usable size variables during construction of the call matrix, can we take the variable for use with SIZELT constraints from the context? Yes, if we are under an inductive constructor. No, if we are under a record constructor.

terUsableVars :: VarSet

Pattern variables that can be compared to argument variables using SIZELT.

defaultTerEnv :: TerEnv Source

An empty termination environment.

Values are set to a safe default meaning that with these initial values the termination checker will not miss termination errors it would have seen with better settings of these values.

Values that do not have a safe default are set to IMPOSSIBLE.

class (Functor m, Monad m) => MonadTer m where Source

Termination monad service class.

Minimal complete definition

terAsk, terLocal

Methods

terAsk :: m TerEnv Source

terLocal :: (TerEnv -> TerEnv) -> m a -> m a Source

terAsks :: (TerEnv -> a) -> m a Source

Instances

runTer :: TerEnv -> TerM a -> TCM a Source

Generic run method for termination monad.

runTerDefault :: TerM a -> TCM a Source

Run TerM computation in default environment (created from options).

Termination monad is a MonadTCM.

Modifiers and accessors for the termination environment in the monad.

terPiGuarded :: TerM a -> TerM a Source

Should the codomain part of a function type preserve guardedness?

withUsableVars :: UsableSizeVars a => a -> TerM b -> TerM b Source

Compute usable vars from patterns and run subcomputation.

conUseSizeLt :: QName -> TerM a -> TerM a Source

Set terUseSizeLt when going under constructor c.

projUseSizeLt :: QName -> TerM a -> TerM a Source

Set terUseSizeLt for arguments following projection q. We disregard j<i after a non-coinductive projection. However, the projection need not be recursive (Issue 1470).

isProjectionButNotCoinductive :: MonadTCM tcm => QName -> tcm Bool Source

For termination checking purposes flat should not be considered a projection. That is, it flat doesn't preserve either structural order or guardedness like other projections do. Andreas, 2012-06-09: the same applies to projections of recursive records.

isCoinductiveProjection :: MonadTCM tcm => Bool -> QName -> tcm Bool Source

Check whether a projection belongs to a coinductive record and is actually recursive. E.g. @ isCoinductiveProjection (Stream.head) = return False

isCoinductiveProjection (Stream.tail) = return True @

De Bruijn patterns.

type DeBruijnPat = DeBruijnPat' Int Source

Patterns with variables as de Bruijn indices.

data DeBruijnPat' a Source

Constructors

VarDBP a

De Bruijn Index.

ConDBP QName [DeBruijnPat' a]

The name refers to either an ordinary constructor or the successor function on sized types.

LitDBP Literal

Literal. Also abused to censor part of a pattern.

TermDBP Term

Part of dot pattern that cannot be converted into a pattern.

ProjDBP QName

Projection pattern.

patternDepth :: DeBruijnPat' a -> Int Source

How long is the path to the deepest variable?

unusedVar :: DeBruijnPat Source

A dummy pattern used to mask a pattern that cannot be used for structural descent.

raiseDBP :: Int -> DeBruijnPats -> DeBruijnPats Source

raiseDBP n ps increases each de Bruijn index in ps by n. Needed when going under a binder during analysis of a term.

class UsableSizeVars a where Source

Extract variables from DeBruijnPats that could witness a decrease via a SIZELT constraint.

These variables must be under an inductive constructor (with no record constructor in the way), or after a coinductive projection (with no inductive one in the way).

Masked patterns (which are not eligible for structural descent, only for size descent)

data Masked a Source

Constructors

Masked 

Fields

getMask :: Bool

True if thing not eligible for structural descent.

getMasked :: a

Thing.

masked :: a -> Masked a Source

Call pathes

newtype CallPath Source

The call information is stored as free monoid over CallInfo. As long as we never look at it, only accumulate it, it does not matter whether we use Set, (nub) list, or Tree. Internally, due to lazyness, it is anyway a binary tree of mappend nodes and singleton leafs. Since we define no order on CallInfo (expensive), we cannot use a Set or nub list. Performance-wise, I could not see a difference between Set and list.

Constructors

CallPath 

Fields

callInfos :: [CallInfo]
 

Instances

Size depth estimation

terSetSizeDepth :: Telescope -> TerM a -> TerM a Source

A very crude way of estimating the SIZELT chains i > j > k in context. Returns 3 in this case. Overapproximates.