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

Safe HaskellNone
LanguageHaskell2010

Agda.TypeChecking.SizedTypes.WarshallSolver

Contents

Synopsis

Documentation

type Graph r f a = Graph (Node r f) a Source #

type Edge' r f a = Edge (Node r f) a Source #

type Key r f = Edge' r f () Source #

type Nodes r f = Nodes (Node r f) Source #

src :: Edge n e -> n Source #

dest :: Edge n e -> n Source #

lookupEdge :: Ord n => Graph n e -> n -> n -> Maybe e Source #

graphToList :: Graph n e -> [Edge n e] Source #

graphFromList :: Ord n => [Edge n e] -> Graph n e Source #

insertEdge :: (Ord n, MeetSemiLattice e, Top e) => Edge n e -> Graph n e -> Graph n e Source #

outgoing :: (Ord r, Ord f) => Graph r f a -> Node r f -> [Edge' r f a] Source #

Compute list of edges that start in a given node.

incoming :: (Ord r, Ord f) => Graph r f a -> Node r f -> [Edge' r f a] Source #

Compute list of edges that target a given node.

Note: expensive for unidirectional graph representations.

setFoldl :: (b -> a -> b) -> b -> Set a -> b Source #

Set.foldl does not exist in legacy versions of the containers package.

transClos :: forall n a. (Ord n, Dioid a) => Graph n a -> Graph n a Source #

Floyd-Warshall algorithm.

Edge weights

data Weight Source #

Constructors

Offset Offset 
Infinity 
Instances
Enum Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Eq Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

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

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

Num Weight Source #

Partial implementation of Num.

Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Ord Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Show Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Dioid Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

MeetSemiLattice Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

meet :: Weight -> Weight -> Weight Source #

Top Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Pretty Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Negative Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Weight -> Bool Source #

Plus Offset Weight Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

plus :: Offset -> Weight -> Weight Source #

Plus Weight Offset Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

plus :: Weight -> Offset -> Weight Source #

Plus (SizeExpr' r f) Weight (SizeExpr' r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

plus :: SizeExpr' r f -> Weight -> SizeExpr' r f Source #

class Negative a where Source #

Test for negativity, used to detect negative cycles.

Minimal complete definition

negative

Methods

negative :: a -> Bool Source #

Instances
Negative Int Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Int -> Bool Source #

Negative Offset Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Offset -> Bool Source #

Negative Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Label -> Bool Source #

Negative Weight Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Weight -> Bool Source #

(Ord r, Ord f, Negative a) => Negative (Graphs r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Graphs r f a -> Bool Source #

Negative a => Negative (Edge' r f a) Source #

An edge is negative if its label is.

Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Edge' r f a -> Bool Source #

(Ord r, Ord f, Negative a) => Negative (Graph r f a) Source #

A graph is negative if it contains a negative loop (diagonal edge). Makes sense on transitive graphs.

Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Graph r f a -> Bool Source #

Edge labels

data Label Source #

Going from Lt to Le is pred, going from Le to Lt is succ.

X --(R,n)--> Y means X (R) Y + n. [ ... if n positive and X + (-n) (R) Y if n negative. ]

Constructors

Label 

Fields

LInf

Nodes not connected.

Instances
Eq Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

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

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

Ord Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

compare :: Label -> Label -> Ordering #

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

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

(>) :: Label -> Label -> Bool #

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

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

Show Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Dioid Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

MeetSemiLattice Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

meet :: Label -> Label -> Label Source #

Top Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Pretty Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Negative Label Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Label -> Bool Source #

(Ord r, Ord f) => SetToInfty f (ConGraph r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> ConGraph r f -> ConGraph r f Source #

Plus (SizeExpr' r f) Label (SizeExpr' r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

plus :: SizeExpr' r f -> Label -> SizeExpr' r f Source #

toWeight :: Label -> Weight Source #

Convert a label to a weight, decrementing in case of Lt.

Semiring with idempotent + == dioid

Graphs

Nodes

data Node rigid flex Source #

Constructors

NodeZero 
NodeInfty 
NodeRigid rigid 
NodeFlex flex 
Instances
(Ord r, Ord f) => SetToInfty f (ConGraph r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> ConGraph r f -> ConGraph r f Source #

Eq f => SetToInfty f (Node r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> Node r f -> Node r f Source #

Eq f => SetToInfty f (Edge' r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> Edge' r f a -> Edge' r f a Source #

(Eq rigid, Eq flex) => Eq (Node rigid flex) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

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

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

(Ord rigid, Ord flex) => Ord (Node rigid flex) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

compare :: Node rigid flex -> Node rigid flex -> Ordering #

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

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

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

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

max :: Node rigid flex -> Node rigid flex -> Node rigid flex #

min :: Node rigid flex -> Node rigid flex -> Node rigid flex #

(Show rigid, Show flex) => Show (Node rigid flex) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

showsPrec :: Int -> Node rigid flex -> ShowS #

show :: Node rigid flex -> String #

showList :: [Node rigid flex] -> ShowS #

(Pretty rigid, Pretty flex) => Pretty (Node rigid flex) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

pretty :: Node rigid flex -> Doc Source #

prettyPrec :: Int -> Node rigid flex -> Doc Source #

prettyList :: [Node rigid flex] -> Doc Source #

(Ord r, Ord f, Dioid a) => Dioid (Edge' r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

compose :: Edge' r f a -> Edge' r f a -> Edge' r f a Source #

unitCompose :: Edge' r f a Source #

(Ord r, Ord f, MeetSemiLattice a) => MeetSemiLattice (Edge' r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

meet :: Edge' r f a -> Edge' r f a -> Edge' r f a Source #

(Ord r, Ord f, Top a) => Top (Edge' r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

top :: Edge' r f a Source #

isTop :: Edge' r f a -> Bool Source #

(Ord r, Ord f, Negative a) => Negative (Graphs r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Graphs r f a -> Bool Source #

Negative a => Negative (Edge' r f a) Source #

An edge is negative if its label is.

Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Edge' r f a -> Bool Source #

(Ord r, Ord f, Negative a) => Negative (Graph r f a) Source #

A graph is negative if it contains a negative loop (diagonal edge). Makes sense on transitive graphs.

Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

negative :: Graph r f a -> Bool Source #

isFlexNode :: Node rigid flex -> Maybe flex Source #

isZeroNode :: Node rigid flex -> Bool Source #

isInftyNode :: Node rigid flex -> Bool Source #

nodeToSizeExpr :: Node rigid flex -> SizeExpr' rigid flex Source #

Edges

Graphs

type Graphs r f a = [Graph r f a] Source #

A graph forest.

mentions :: (Ord r, Ord f) => Node r f -> Graphs r f a -> (Graphs r f a, Graphs r f a) Source #

Split a list of graphs gs into those that mention node n and those that do not. If n is zero or infinity, we regard it as "not mentioned".

addEdge :: (Ord r, Ord f, MeetSemiLattice a, Top a) => Edge' r f a -> Graphs r f a -> Graphs r f a Source #

Add an edge to a graph forest. Graphs that share a node with the edge are joined.

reflClos :: (Ord r, Ord f, Dioid a) => Set (Node r f) -> Graph r f a -> Graph r f a Source #

Reflexive closure. Add edges 0 -> n -> n -> oo for all nodes n.

implies :: (Ord r, Ord f, Pretty r, Pretty f, Pretty a, Top a, Ord a, Negative a) => Graph r f a -> Graph r f a -> Bool Source #

h implies g if any edge in g between rigids and constants is implied by a corresponding edge in h, which means that the edge in g carries at most the information of the one in h.

Application: Constraint implication: Constraints are compatible with hypotheses.

nodeFromSizeExpr :: SizeExpr' rigid flex -> (Node rigid flex, Offset) Source #

edgeFromConstraint :: Constraint' rigid flex -> LabelledEdge rigid flex Source #

graphFromConstraints :: (Ord rigid, Ord flex) => [Constraint' rigid flex] -> Graph rigid flex Label Source #

Build a graph from list of simplified constraints.

graphsFromConstraints :: (Ord rigid, Ord flex) => [Constraint' rigid flex] -> Graphs rigid flex Label Source #

Build a graph from list of simplified constraints.

type HypGraph r f = Graph r f Label Source #

hypGraph :: (Ord rigid, Ord flex, Pretty rigid, Pretty flex) => Set rigid -> [Hyp' rigid flex] -> Either String (HypGraph rigid flex) Source #

hypConn :: (Ord r, Ord f) => HypGraph r f -> Node r f -> Node r f -> Label Source #

simplifyWithHypotheses :: (Ord rigid, Ord flex, Pretty rigid, Pretty flex) => HypGraph rigid flex -> [Constraint' rigid flex] -> Either String [Constraint' rigid flex] Source #

type ConGraph r f = Graph r f Label Source #

type ConGraphs r f = Graphs r f Label Source #

constraintGraphs :: (Ord r, Ord f, Pretty r, Pretty f) => [Constraint' r f] -> HypGraph r f -> Either String ([f], ConGraphs r f) Source #

infinityFlexs :: (Ord r, Ord f) => ConGraph r f -> ([f], ConGraph r f) Source #

If we have an edge X + n <= X (with n >= 0), we must set X = oo.

class SetToInfty f a where Source #

Minimal complete definition

setToInfty

Methods

setToInfty :: [f] -> a -> a Source #

Instances
(Ord r, Ord f) => SetToInfty f (ConGraph r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> ConGraph r f -> ConGraph r f Source #

Eq f => SetToInfty f (Node r f) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> Node r f -> Node r f Source #

Eq f => SetToInfty f (Edge' r f a) Source # 
Instance details

Defined in Agda.TypeChecking.SizedTypes.WarshallSolver

Methods

setToInfty :: [f] -> Edge' r f a -> Edge' r f a Source #

Compute solution from constraint graph.

type Bound r f = Map f (Set (SizeExpr' r f)) Source #

Lower or upper bound for a flexible variable

data Bounds r f Source #

Constructors

Bounds 

Fields

edgeToLowerBound :: LabelledEdge r f -> Maybe (f, SizeExpr' r f) Source #

Compute a lower bound for a flexible from an edge.

edgeToUpperBound :: LabelledEdge r f -> Maybe (f, Cmp, SizeExpr' r f) Source #

Compute an upper bound for a flexible from an edge.

graphToLowerBounds :: (Ord r, Ord f) => [LabelledEdge r f] -> Bound r f Source #

Compute the lower bounds for all flexibles in a graph.

graphToUpperBounds :: (Ord r, Ord f) => [LabelledEdge r f] -> (Bound r f, Set f) Source #

Compute the upper bounds for all flexibles in a graph.

bounds :: (Ord r, Ord f) => ConGraph r f -> Bounds r f Source #

Compute the bounds for all flexibles in a graph.

smallest :: (Ord r, Ord f) => HypGraph r f -> [Node r f] -> [Node r f] Source #

Compute the relative minima in a set of nodes (those that do not have a predecessor in the set).

largest :: (Ord r, Ord f) => HypGraph r f -> [Node r f] -> [Node r f] Source #

Compute the relative maxima in a set of nodes (those that do not have a successor in the set).

commonSuccs :: (Ord r, Ord f) => Graph r f a -> [Node r f] -> Map (Node r f) [Edge' r f a] Source #

Given source nodes n1,n2,... find all target nodes m1,m2, such that for all j, there are edges n_i --l_ij--> m_j for all i. Return these edges as a map from target notes to a list of edges. We assume the graph is reflexive-transitive.

commonPreds :: (Ord r, Ord f) => Graph r f a -> [Node r f] -> Map (Node r f) [Edge' r f a] Source #

Given target nodes m1,m2,... find all source nodes n1,n2, such that for all j, there are edges n_i --l_ij--> m_j for all i. Return these edges as a map from target notes to a list of edges. We assume the graph is reflexive-transitive.

lub' :: forall r f. (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => HypGraph r f -> (Node r f, Offset) -> (Node r f, Offset) -> Maybe (SizeExpr' r f) Source #

Compute the sup of two different rigids or a rigid and a constant.

glb' :: forall r f. (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => HypGraph r f -> (Node r f, Offset) -> (Node r f, Offset) -> Maybe (SizeExpr' r f) Source #

Compute the inf of two different rigids or a rigid and a constant.

lub :: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => HypGraph r f -> SizeExpr' r f -> SizeExpr' r f -> Maybe (SizeExpr' r f) Source #

Compute the least upper bound (sup).

glb :: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => HypGraph r f -> SizeExpr' r f -> SizeExpr' r f -> Maybe (SizeExpr' r f) Source #

Compute the greatest lower bound (inf) of size expressions relative to a hypotheses graph.

findRigidBelow :: (Ord r, Ord f) => HypGraph r f -> SizeExpr' r f -> Maybe (SizeExpr' r f) Source #

solveGraph :: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => Polarities f -> HypGraph r f -> ConGraph r f -> Either String (Solution r f) Source #

solveGraphs :: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => Polarities f -> HypGraph r f -> ConGraphs r f -> Either String (Solution r f) Source #

Solve a forest of constraint graphs relative to a hypotheses graph. Concatenate individual solutions.

Verify solution

verifySolution :: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) => HypGraph r f -> [Constraint' r f] -> Solution r f -> Either String () Source #

Check that after substitution of the solution, constraints are implied by hypotheses.

iterateSolver Source #

Arguments

:: (Ord r, Ord f, Pretty r, Pretty f, Show r, Show f) 
=> Polarities f

Meta variable polarities (prefer lower or upper solution?).

-> HypGraph r f

Hypotheses (assumed to have no metas, so, fixed during iteration).

-> [Constraint' r f]

Constraints to solve.

-> Solution r f

Previous substitution (already applied to constraints).

-> Either String (Solution r f)

Accumulated substition.

Iterate solver until no more metas can be solved.

This might trigger a (wanted) error on the second iteration (see Issue 2096) which would otherwise go unnoticed.

Tests

testLub :: (Pretty f, Ord f, Show f) => Maybe (SizeExpr' [Char] f) Source #