MiniAgda
Safe HaskellNone
LanguageHaskell98

Warshall

Documentation

traceSolve :: String -> a -> a Source #

traceSolveM :: Monad m => String -> m () Source #

class SemiRing a where Source #

Methods

oplus :: a -> a -> a Source #

otimes :: a -> a -> a Source #

ozero :: a Source #

oone :: a Source #

Instances

Instances details
SemiRing PPoly Source # 
Instance details

Defined in Polarity

SemiRing Pol Source # 
Instance details

Defined in Polarity

SemiRing Weight Source # 
Instance details

Defined in Warshall

type Matrix a = Array (Int, Int) a Source #

data Weight Source #

Constructors

Finite Int 
Infinite 

Instances

Instances details
SemiRing Weight Source # 
Instance details

Defined in Warshall

Show Constraint Source # 
Instance details

Defined in Warshall

Show Weight Source # 
Instance details

Defined in Warshall

Eq Weight Source # 
Instance details

Defined in Warshall

Methods

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

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

Ord Weight Source # 
Instance details

Defined in Warshall

data Node rigid Source #

Constructors

Rigid rigid 
Flex FlexId 

Instances

Instances details
Show rigid => Show (Node rigid) Source # 
Instance details

Defined in Warshall

Methods

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

show :: Node rigid -> String #

showList :: [Node rigid] -> ShowS #

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

Defined in Warshall

Methods

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

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

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

Defined in Warshall

Methods

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

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

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

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

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

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

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

data Rigid Source #

Constructors

RConst Weight 
RVar RigidId 

Instances

Instances details
Show Constraint Source # 
Instance details

Defined in Warshall

Show Rigid Source # 
Instance details

Defined in Warshall

Methods

showsPrec :: Int -> Rigid -> ShowS #

show :: Rigid -> String #

showList :: [Rigid] -> ShowS #

Eq Rigid Source # 
Instance details

Defined in Warshall

Methods

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

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

Ord Rigid Source # 
Instance details

Defined in Warshall

Methods

compare :: Rigid -> Rigid -> Ordering #

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

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

(>) :: Rigid -> Rigid -> Bool #

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

max :: Rigid -> Rigid -> Rigid #

min :: Rigid -> Rigid -> Rigid #

data Constrnt edgeLabel rigid flexScope Source #

Constructors

NewFlex FlexId flexScope 
Arc (Node rigid) edgeLabel (Node rigid) 

Instances

Instances details
Show Constraint Source # 
Instance details

Defined in Warshall

data Graph edgeLabel rigid flexScope Source #

Constructors

Graph 

Fields

initGraph :: SemiRing edgeLabel => Graph edgeLabel rigid flexScope Source #

type GM edgeLabel rigid flexScope = State (Graph edgeLabel rigid flexScope) Source #

addFlex :: FlexId -> flexScope -> GM edgeLabel rigid flexScope () Source #

addNode :: (Eq rigid, Ord rigid) => Node rigid -> GM edgeLabel rigid flexScope Int Source #

addEdge :: (Eq rigid, Ord rigid, SemiRing edgeLabel) => Node rigid -> edgeLabel -> Node rigid -> GM edgeLabel rigid flexScope () Source #

addConstraint :: (Eq rigid, Ord rigid, SemiRing edgeLabel) => Constrnt edgeLabel rigid flexScope -> GM edgeLabel rigid flexScope () Source #

buildGraph :: (Eq rigid, Ord rigid, SemiRing edgeLabel) => [Constrnt edgeLabel rigid flexScope] -> Graph edgeLabel rigid flexScope Source #

mkMatrix :: Int -> (Int -> Int -> a) -> Matrix a Source #

data LegendMatrix a b c Source #

Constructors

LegendMatrix 

Fields

Instances

Instances details
(Show a, Show b, Show c) => Show (LegendMatrix a b c) Source # 
Instance details

Defined in Warshall

Methods

showsPrec :: Int -> LegendMatrix a b c -> ShowS #

show :: LegendMatrix a b c -> String #

showList :: [LegendMatrix a b c] -> ShowS #

data SizeExpr Source #

Constructors

SizeVar Int Int 
SizeConst Weight 

Instances

Instances details
Show SizeExpr Source # 
Instance details

Defined in Warshall