| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Agda.TypeChecking.SizedTypes.Syntax
Contents
Description
Syntax of size expressions and constraints.
- newtype Offset = O Int
- newtype Rigid = RigidId {}
- newtype Flex = FlexId {}
- data SizeExpr' rigid flex
- type SizeExpr = SizeExpr' Rigid Flex
- data Cmp
- data Constraint' rigid flex = Constraint {}
- type Constraint = Constraint' Rigid Flex
- data Polarity
- data PolarityAssignment flex = PolarityAssignment Polarity flex
- type Polarities flex = Map flex Polarity
- emptyPolarities :: Polarities flex
- polaritiesFromAssignments :: Ord flex => [PolarityAssignment flex] -> Polarities flex
- getPolarity :: Ord flex => Polarities flex -> flex -> Polarity
- type Solution rigid flex = Map flex (SizeExpr' rigid flex)
- class Substitute r f a where
- type CTrans r f = Constraint' r f -> Either String [Constraint' r f]
- simplify1 :: (Show f, Show r, Eq r) => CTrans r f -> CTrans r f
- ifLe :: Cmp -> a -> a -> a
- compareOffset :: Offset -> Cmp -> Offset -> Bool
- class ValidOffset a where
- class TruncateOffset a where
- class Rigids r a where
- class Flexs flex a | a -> flex where
Syntax
Constant finite sizes n >= 0.
Instances
| Enum Offset Source # | |
| Eq Offset Source # | |
| Num Offset Source # | |
| Ord Offset Source # | |
| Show Offset Source # | |
| MeetSemiLattice Offset Source # | |
| TruncateOffset Offset Source # | |
| ValidOffset Offset Source # | |
| Negative Offset Source # | |
| Plus Offset Offset Offset Source # | |
| Plus Offset Weight Weight Source # | |
| Plus Weight Offset Weight Source # | |
| Plus (SizeExpr' r f) Offset (SizeExpr' r f) Source # | Add offset to size expression. |
Fixed size variables i.
Size meta variables X to solve for.
data SizeExpr' rigid flex Source #
Size expressions appearing in constraints.
Constructors
| Const | Constant number |
| Rigid | Variable plus offset |
| Infty | Infinity |
| Flex | Meta variable |
Instances
| Ord f => Substitute r f (SizeExpr' r f) Source # | |
| Flexs flex (SizeExpr' rigid flex) Source # | |
| Rigids r (SizeExpr' r f) Source # | |
| Subst Term (SizeExpr' NamedRigid SizeMeta) Source # | Only for |
| Functor (SizeExpr' rigid) Source # | |
| Foldable (SizeExpr' rigid) Source # | |
| Traversable (SizeExpr' rigid) Source # | |
| (Eq flex, Eq rigid) => Eq (SizeExpr' rigid flex) Source # | |
| (Ord flex, Ord rigid) => Ord (SizeExpr' rigid flex) Source # | |
| (Show r, Show f) => Show (SizeExpr' r f) Source # | |
| TruncateOffset (SizeExpr' r f) Source # | |
| ValidOffset (SizeExpr' r f) Source # | |
| Plus (SizeExpr' r f) Offset (SizeExpr' r f) Source # | Add offset to size expression. |
| Plus (SizeExpr' r f) Label (SizeExpr' r f) Source # | |
| Plus (SizeExpr' r f) Weight (SizeExpr' r f) Source # | |
Comparison operator, e.g. for size expression.
data Constraint' rigid flex Source #
Constraint: an inequation between size expressions,
e.g. X < ∞ or i + 3 ≤ j.
Constructors
| Constraint | |
Instances
| PrettyTCM SizeConstraint Source # | Assumes we are in the right context. |
| Subst Term SizeConstraint Source # | |
| Ord f => Substitute r f (Constraint' r f) Source # | |
| Ord flex => Flexs flex (Constraint' rigid flex) Source # | |
| Ord r => Rigids r (Constraint' r f) Source # | |
| Functor (Constraint' rigid) Source # | |
| Foldable (Constraint' rigid) Source # | |
| Traversable (Constraint' rigid) Source # | |
| (Show r, Show f) => Show (Constraint' r f) Source # | |
type Constraint = Constraint' Rigid Flex Source #
Polarities to specify solutions.
What type of solution are we looking for?
data PolarityAssignment flex Source #
Assigning a polarity to a flexible variable.
Constructors
| PolarityAssignment Polarity flex |
Instances
| Show flex => Show (PolarityAssignment flex) Source # | |
type Polarities flex = Map flex Polarity Source #
Type of solution wanted for each flexible.
emptyPolarities :: Polarities flex Source #
polaritiesFromAssignments :: Ord flex => [PolarityAssignment flex] -> Polarities flex Source #
getPolarity :: Ord flex => Polarities flex -> flex -> Polarity Source #
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 where Source #
Executing a substitution.
Minimal complete definition
Instances
| Substitute r f a => Substitute r f [a] Source # | |
| Substitute r f a => Substitute r f (Map k a) Source # | |
| Ord f => Substitute r f (Constraint' r f) Source # | |
| Ord f => Substitute r f (SizeExpr' r f) Source # | |
Constraint simplification
type CTrans r f = Constraint' r f -> Either String [Constraint' r f] Source #
simplify1 :: (Show f, Show r, Eq r) => CTrans r f -> CTrans r f Source #
Returns an error message if we have a contradictory constraint.
Printing
Wellformedness
class ValidOffset a where Source #
Offsets + n must be non-negative
Minimal complete definition
Methods
validOffset :: a -> Bool Source #
Instances
| ValidOffset Offset Source # | |
| ValidOffset (SizeExpr' r f) Source # | |
class TruncateOffset a where Source #
Make offsets non-negative by rounding up.
Minimal complete definition
Methods
truncateOffset :: a -> a Source #
Instances
Computing variable sets
class Rigids r a where Source #
The rigid variables contained in a pice of syntax.
Minimal complete definition