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

Safe HaskellNone
LanguageHaskell98

Agda.Termination.Order

Contents

Description

An Abstract domain of relative sizes, i.e., differences between size of formal function parameter and function argument in recursive call; used in the termination checker.

Synopsis

Structural orderings

data Order Source #

In the paper referred to above, there is an order R with Unknown <= Le <= Lt.

This is generalized to Unknown <= 'Decr k' where Decr 1 replaces Lt and Decr 0 replaces Le. A negative decrease means an increase. The generalization allows the termination checker to record an increase by 1 which can be compensated by a following decrease by 2 which results in an overall decrease.

However, the termination checker of the paper itself terminates because there are only finitely many different call-matrices. To maintain termination of the terminator we set a cutoff point which determines how high the termination checker can count. This value should be set by a global or file-wise option.

See Call for more information.

TODO: document orders which are call-matrices themselves.

Constructors

Mat !(Matrix Int Order)

Matrix-shaped order, currently UNUSED.

Instances

Eq Order Source # 

Methods

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

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

Ord Order Source # 

Methods

compare :: Order -> Order -> Ordering #

(<) :: Order -> Order -> Bool #

(<=) :: Order -> Order -> Bool #

(>) :: Order -> Order -> Bool #

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

max :: Order -> Order -> Order #

min :: Order -> Order -> Order #

Show Order Source # 

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Arbitrary Order Source # 

Methods

arbitrary :: Gen Order #

shrink :: Order -> [Order] #

Arbitrary CallMatrix # 
CoArbitrary Order Source # 

Methods

coarbitrary :: Order -> Gen b -> Gen b #

PartialOrd Order Source #

Information order: Unknown is least information. The more we decrease, the more information we have.

When having comparable call-matrices, we keep the lesser one. Call graph completion works toward losing the good calls, tending towards Unknown (the least information).

HasZero Order Source # 
Pretty Order Source # 
Pretty CallMatrix Source # 
NotWorse Order Source #

It does not get worse then `increase'. If we are still decreasing, it can get worse: less decreasing.

Methods

notWorse :: Order -> Order -> Bool Source #

CallComb CallMatrix Source #

Call matrix multiplication.

f --(m1)--> g --(m2)--> h is combined to f --(m2 mul m1)--> h

Note the reversed order of multiplication: The matrix c1 of the second call g-->h in the sequence f-->g-->h is multiplied with the matrix c2 of the first call.

Preconditions: m1 has dimensions ar(g) × ar(f). m2 has dimensions ar(h) × ar(g).

Postcondition: m1 >*< m2 has dimensions ar(h) × ar(f).

NotWorse (CallMatrix' Order) Source # 
Diagonal (CallMatrixAug cinfo) Order Source # 

Methods

diagonal :: CallMatrixAug cinfo -> [Order] Source #

Ord i => NotWorse (Matrix i Order) Source #

We assume the matrices have the same dimension.

decr :: (?cutoff :: CutOff) => Int -> Order Source #

Smart constructor for Decr k :: Order which cuts off too big values.

Possible values for k: - ?cutoff <= k <= ?cutoff + 1.

increase :: Int -> Order -> Order Source #

Raw increase which does not cut off.

decrease :: Int -> Order -> Order Source #

Raw decrease which does not cut off.

(.*.) :: (?cutoff :: CutOff) => Order -> Order -> Order Source #

Multiplication of Orders. (Corresponds to sequential composition.)

supremum :: (?cutoff :: CutOff) => [Order] -> Order Source #

The supremum of a (possibly empty) list of Orders. More information (i.e., more decrease) is bigger. Unknown is no information, thus, smallest.

infimum :: (?cutoff :: CutOff) => [Order] -> Order Source #

The infimum of a (non empty) list of Orders. Unknown is the least element, thus, dominant.

le :: Order Source #

le, lt, decreasing, unknown: for backwards compatibility, and for external use.

orderMat :: Matrix Int Order -> Order Source #

Smart constructor for matrix shaped orders, avoiding empty and singleton matrices.

collapseO :: (?cutoff :: CutOff) => Order -> Order Source #

isDecr :: Order -> Bool Source #

Matrix-shaped order is decreasing if any diagonal element is decreasing.

class NotWorse a where Source #

A partial order, aimed at deciding whether a call graph gets worse during the completion.

Minimal complete definition

notWorse

Methods

notWorse :: a -> a -> Bool Source #

Instances

NotWorse Order Source #

It does not get worse then `increase'. If we are still decreasing, it can get worse: less decreasing.

Methods

notWorse :: Order -> Order -> Bool Source #

NotWorse (CallMatrixAug cinfo) Source # 

Methods

notWorse :: CallMatrixAug cinfo -> CallMatrixAug cinfo -> Bool Source #

NotWorse (CallMatrix' Order) Source # 
Ord i => NotWorse (Matrix i Order) Source #

We assume the matrices have the same dimension.