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

Safe HaskellNone

Agda.TypeChecking.SizedTypes.Syntax

Contents

Description

Syntax of size expressions and constraints.

Synopsis

Syntax

type Offset = IntSource

Constant finite sizes n >= 0.

newtype Rigid Source

Fixed size variables i.

Constructors

RigidId 

Fields

rigidId :: String
 

Instances

Eq Rigid 
Ord Rigid 
Show Rigid 

newtype Flex Source

Size meta variables X to solve for.

Constructors

FlexId 

Fields

flexId :: String
 

Instances

Eq Flex 
Ord Flex 
Show Flex 

data SizeExpr' rigid flex Source

Size expressions appearing in constraints.

Constructors

Const

Constant number n.

Fields

offset :: Offset
 
Rigid

Variable plus offset i + n.

Fields

rigid :: rigid
 
offset :: Offset
 
Infty

Infinity .

Flex

Meta variable X + n.

Fields

flex :: flex
 
offset :: Offset
 

Instances

Ord f => Substitute r f (SizeExpr' r f) 
Ord flex => Flexs flex (SizeExpr' rigid flex) 
Rigids r (SizeExpr' r f) 
Functor (SizeExpr' rigid) 
Foldable (SizeExpr' rigid) 
Traversable (SizeExpr' rigid) 
(Eq rigid, Eq flex) => Eq (SizeExpr' rigid flex) 
(Ord rigid, Ord flex) => Ord (SizeExpr' rigid flex) 
(Show r, Show f) => Show (SizeExpr' r f) 
TruncateOffset (SizeExpr' r f) 
ValidOffset (SizeExpr' r f) 
Subst (SizeExpr' NamedRigid SizeMeta)

Only for raise.

Plus (SizeExpr' r f) Offset (SizeExpr' r f)

Add offset to size expression.

Plus (SizeExpr' r f) Label (SizeExpr' r f) 
Plus (SizeExpr' r f) Weight (SizeExpr' r f) 

data Cmp Source

Comparison operator, e.g. for size expression.

Constructors

Lt

<.

Le

.

Instances

Bounded Cmp 
Enum Cmp 
Eq Cmp 
Ord Cmp

Comparison operator is ordered Lt < Le.

Show Cmp 
Arbitrary Cmp 
Dioid Cmp 
MeetSemiLattice Cmp 
Top Cmp 
AsWeightRelation Cmp 

data Constraint' rigid flex Source

Constraint: an inequation between size expressions, e.g. X < ∞ or i + 3 ≤ j.

Constructors

Constraint 

Fields

leftExpr :: SizeExpr' rigid flex
 
cmp :: Cmp
 
rightExpr :: SizeExpr' rigid flex
 

Instances

Subst SizeConstraint 
PrettyTCM SizeConstraint

Assumes we are in the right context.

Ord f => Substitute r f (Constraint' r f) 
Ord flex => Flexs flex (Constraint' rigid flex) 
Ord r => Rigids r (Constraint' r f) 
Functor (Constraint' rigid) 
Foldable (Constraint' rigid) 
Traversable (Constraint' rigid) 
(Show r, Show f) => Show (Constraint' r f) 

Polarities to specify solutions.

data Polarity Source

What type of solution are we looking for?

Constructors

Least 
Greatest 

Instances

Eq Polarity 
Ord Polarity 
Show Polarity 

data PolarityAssignment flex Source

Assigning a polarity to a flexible variable.

Constructors

PolarityAssignment Polarity flex 

Instances

Show flex => Show (PolarityAssignment flex) 

type Polarities flex = Map flex PolaritySource

Type of solution wanted for each flexible.

getPolarity :: Ord flex => Polarities flex -> flex -> PolaritySource

Default polarity is Least.

Solutions.

type Solution rigid flex = Map flex (SizeExpr' rigid flex)Source

Partial substitution from flexible variables to size expression.

class Substitute r f a whereSource

Executing a substitution.

Methods

subst :: Solution r f -> a -> aSource

Instances

Substitute r f a => Substitute r f [a] 
Ord f => Substitute r f (Constraint' r f) 
Ord f => Substitute r f (SizeExpr' r f) 

Constraint simplification

type CTrans r f = Constraint' r f -> Maybe [Constraint' r f]Source

simplify1 :: Eq r => CTrans r f -> CTrans r fSource

Returns Nothing if we have a contradictory constraint.

ifLe :: Cmp -> a -> a -> aSource

Le acts as True, Lt as False.

compareOffset :: Offset -> Cmp -> Offset -> BoolSource

Interpret Cmp as relation on Offset.

Printing

Wellformedness

class ValidOffset a whereSource

Offsets + n must be non-negative

Methods

validOffset :: a -> BoolSource

class TruncateOffset a whereSource

Make offsets non-negative by rounding up.

Methods

truncateOffset :: a -> aSource

Computing variable sets

class Rigids r a whereSource

The rigid variables contained in a pice of syntax.

Methods

rigids :: a -> Set rSource

Instances

(Ord r, Rigids r a) => Rigids r [a] 
Ord r => Rigids r (Constraint' r f) 
Rigids r (SizeExpr' r f) 

class Flexs flex a | a -> flex whereSource

The flexibe variables contained in a pice of syntax.

Methods

flexs :: a -> Set flexSource

Instances

Flexs SizeMeta HypSizeConstraint 
(Ord flex, Flexs flex a) => Flexs flex [a] 
Ord flex => Flexs flex (Constraint' rigid flex) 
Ord flex => Flexs flex (SizeExpr' rigid flex)