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

Safe HaskellNone
LanguageHaskell2010

Agda.TypeChecking.Positivity

Contents

Description

Check that a datatype is strictly positive.

Synopsis

Documentation

type Graph n e = Graph n n e Source #

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

Check that the datatypes in the mutual block containing the given declarations are strictly positive.

Also add information about positivity and recursivity of records to the signature.

data Item Source #

Constructors

AnArg Nat 
ADef QName 

Instances

Eq Item Source # 

Methods

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

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

Ord Item Source # 

Methods

compare :: Item -> Item -> Ordering #

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

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

(>) :: Item -> Item -> Bool #

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

max :: Item -> Item -> Item #

min :: Item -> Item -> Item #

Show Item Source # 

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

HasRange Item Source # 

Methods

getRange :: Item -> Range Source #

data OccurrencesBuilder Source #

Used to build Occurrences and occurrence graphs.

Constructors

Concat [OccurrencesBuilder] 
OccursAs Where OccurrencesBuilder 
OccursHere Item 
OnlyVarsUpTo Nat OccurrencesBuilder

OnlyVarsUpTo n occs discards occurrences of de Bruijn index >= n.

preprocess :: OccurrencesBuilder -> OccurrencesBuilder' Source #

Removes OnlyVarsUpTo entries and adds OccursWhere entries.

WARNING: There can be lots of sharing between the generated OccursWhere entries. Traversing all of these entries could be expensive. (See computeEdges for an example.)

data OccursWheres Source #

A type used locally in flatten.

flatten :: OccurrencesBuilder -> Occurrences Source #

An interpreter for OccurrencesBuilder.

WARNING: There can be lots of sharing between the generated OccursWhere entries. Traversing all of these entries could be expensive. (See computeEdges for an example.)

data OccEnv Source #

Context for computing occurrences.

Constructors

OccEnv 

Fields

type OccM = Reader OccEnv Source #

Monad for computing occurrences.

class ComputeOccurrences a where Source #

Minimal complete definition

occurrences

Instances

ComputeOccurrences Clause Source # 
ComputeOccurrences LevelAtom Source # 
ComputeOccurrences PlusLevel Source # 
ComputeOccurrences Level Source # 
ComputeOccurrences Type Source # 
ComputeOccurrences Term Source # 
ComputeOccurrences a => ComputeOccurrences [a] Source # 
ComputeOccurrences a => ComputeOccurrences (Maybe a) Source # 
ComputeOccurrences a => ComputeOccurrences (Dom a) Source # 
ComputeOccurrences a => ComputeOccurrences (Arg a) Source # 
ComputeOccurrences a => ComputeOccurrences (Tele a) Source # 
ComputeOccurrences a => ComputeOccurrences (Abs a) Source # 
ComputeOccurrences a => ComputeOccurrences (Elim' a) Source # 
(ComputeOccurrences a, ComputeOccurrences b) => ComputeOccurrences (a, b) Source # 

computeOccurrences :: QName -> TCM Occurrences Source #

Computes the occurrences in the given definition.

WARNING: There can be lots of sharing between the OccursWhere entries. Traversing all of these entries could be expensive. (See computeEdges for an example.)

computeOccurrences' :: QName -> TCM OccurrencesBuilder Source #

Computes the occurrences in the given definition.

etaExpandClause :: Nat -> Clause -> Clause Source #

Eta expand a clause to have the given number of variables. Warning: doesn't put correct types in telescope! This is used instead of special treatment of lambdas (which was unsound: issue 121)

data Node Source #

Constructors

DefNode !QName 
ArgNode !QName !Nat 

Instances

Eq Node Source # 

Methods

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

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

Ord Node Source # 

Methods

compare :: Node -> Node -> Ordering #

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

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

(>) :: Node -> Node -> Bool #

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

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node Source # 

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

PrettyTCM Node Source # 

Methods

prettyTCM :: Node -> TCM Doc Source #

data Edge Source #

Edge labels for the positivity graph.

Constructors

Edge !Occurrence OccursWhere 

Instances

Eq Edge Source # 

Methods

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

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

Ord Edge Source # 

Methods

compare :: Edge -> Edge -> Ordering #

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

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

(>) :: Edge -> Edge -> Bool #

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

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Show Edge Source # 

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

StarSemiRing Edge Source #

As OccursWhere does not have an oplus we cannot do something meaningful for the OccursWhere here.

E.g. ostar (Edge JustNeg w) = Edge Mixed (w oplus (w >*< w)) would probably more sense, if we could do it.

Methods

ostar :: Edge -> Edge Source #

SemiRing Edge Source #

These operations form a semiring if we quotient by the relation "the Occurrence components are equal".

Null Edge Source # 
PrettyTCM n => PrettyTCM (WithNode n Edge) Source # 

buildOccurrenceGraph :: Set QName -> TCM (Graph Node Edge) Source #

WARNING: There can be lots of sharing between the OccursWhere entries in the edges. Traversing all of these entries could be expensive. (See computeEdges for an example.)

computeEdges Source #

Arguments

:: Set QName

The names in the current mutual block.

-> QName

The current name.

-> OccurrencesBuilder 
-> TCM [Edge Node Node Edge] 

Computes all non-ozero occurrence graph edges represented by the given OccurrencesBuilder.

WARNING: There can be lots of sharing between the OccursWhere entries in the edges. Traversing all of these entries could be expensive. For instance, for the function F in benchmarkmiscSlowOccurrences.agda a large number of edges from the argument X to the function F are computed. These edges have polarity StrictPos, JustNeg or JustPos, and contain the following OccursWhere elements:

Orphan instances