sop-satisfier-0.3.4.5: Check satisfiability of expressions on natural numbers
Safe HaskellSafe-Inferred
LanguageHaskell2010

SoPSat.Internal.SoP

Synopsis

Documentation

data Atom f c Source #

Atomic part of a SoP like constants and unknown functions

Constructors

C c

Constant

F f [SoP f c]

Unknown function

Instances

Instances details
(Show f, Show c) => Show (Atom f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

showsPrec :: Int -> Atom f c -> ShowS #

show :: Atom f c -> String #

showList :: [Atom f c] -> ShowS #

(Eq c, Eq f) => Eq (Atom f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

(==) :: Atom f c -> Atom f c -> Bool #

(/=) :: Atom f c -> Atom f c -> Bool #

(Ord c, Ord f) => Ord (Atom f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

compare :: Atom f c -> Atom f c -> Ordering #

(<) :: Atom f c -> Atom f c -> Bool #

(<=) :: Atom f c -> Atom f c -> Bool #

(>) :: Atom f c -> Atom f c -> Bool #

(>=) :: Atom f c -> Atom f c -> Bool #

max :: Atom f c -> Atom f c -> Atom f c #

min :: Atom f c -> Atom f c -> Atom f c #

data Symbol f c Source #

The most basic part used during reasoning: - Numbers - Atoms - Exponents

Constructors

I Integer

Number in an expression

A (Atom f c)

Atom in an expression

E (SoP f c) (Product f c)

Exponentiation

Instances

Instances details
(Ord f, Ord c) => ToSoP f c (Symbol f c) Source # 
Instance details

Defined in SoPSat.SoP

Methods

toSoP :: Symbol f c -> SoP f c Source #

(Show f, Show c) => Show (Symbol f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

showsPrec :: Int -> Symbol f c -> ShowS #

show :: Symbol f c -> String #

showList :: [Symbol f c] -> ShowS #

(Eq c, Eq f) => Eq (Symbol f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

(==) :: Symbol f c -> Symbol f c -> Bool #

(/=) :: Symbol f c -> Symbol f c -> Bool #

(Ord c, Ord f) => Ord (Symbol f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

compare :: Symbol f c -> Symbol f c -> Ordering #

(<) :: Symbol f c -> Symbol f c -> Bool #

(<=) :: Symbol f c -> Symbol f c -> Bool #

(>) :: Symbol f c -> Symbol f c -> Bool #

(>=) :: Symbol f c -> Symbol f c -> Bool #

max :: Symbol f c -> Symbol f c -> Symbol f c #

min :: Symbol f c -> Symbol f c -> Symbol f c #

newtype Product f c Source #

Product of symbols

Constructors

P 

Fields

Instances

Instances details
(Ord f, Ord c) => ToSoP f c (Product f c) Source # 
Instance details

Defined in SoPSat.SoP

Methods

toSoP :: Product f c -> SoP f c Source #

(Show f, Show c) => Show (Product f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

showsPrec :: Int -> Product f c -> ShowS #

show :: Product f c -> String #

showList :: [Product f c] -> ShowS #

(Eq f, Eq c) => Eq (Product f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

(==) :: Product f c -> Product f c -> Bool #

(/=) :: Product f c -> Product f c -> Bool #

(Ord f, Ord c) => Ord (Product f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

compare :: Product f c -> Product f c -> Ordering #

(<) :: Product f c -> Product f c -> Bool #

(<=) :: Product f c -> Product f c -> Bool #

(>) :: Product f c -> Product f c -> Bool #

(>=) :: Product f c -> Product f c -> Bool #

max :: Product f c -> Product f c -> Product f c #

min :: Product f c -> Product f c -> Product f c #

newtype SoP f c Source #

Sum of Products

Constructors

S 

Fields

Instances

Instances details
(Ord f, Ord c) => ToSoP f c (SoP f c) Source # 
Instance details

Defined in SoPSat.SoP

Methods

toSoP :: SoP f c -> SoP f c Source #

(Show f, Show c) => Show (SoP f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

showsPrec :: Int -> SoP f c -> ShowS #

show :: SoP f c -> String #

showList :: [SoP f c] -> ShowS #

(Eq f, Eq c) => Eq (SoP f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

(==) :: SoP f c -> SoP f c -> Bool #

(/=) :: SoP f c -> SoP f c -> Bool #

(Ord f, Ord c) => Ord (SoP f c) Source # 
Instance details

Defined in SoPSat.Internal.SoP

Methods

compare :: SoP f c -> SoP f c -> Ordering #

(<) :: SoP f c -> SoP f c -> Bool #

(<=) :: SoP f c -> SoP f c -> Bool #

(>) :: SoP f c -> SoP f c -> Bool #

(>=) :: SoP f c -> SoP f c -> Bool #

max :: SoP f c -> SoP f c -> SoP f c #

min :: SoP f c -> SoP f c -> SoP f c #

mergeWith :: (a -> a -> Either a a) -> [a] -> [a] Source #

reduceExp :: (Ord f, Ord c) => Symbol f c -> Symbol f c Source #

mergeS :: (Ord f, Ord c) => Symbol f c -> Symbol f c -> Either (Symbol f c) (Symbol f c) Source #

mergeP :: (Eq f, Eq c) => Product f c -> Product f c -> Either (Product f c) (Product f c) Source #

normaliseExp :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c Source #

mkNonEmpty :: (Ord f, Ord c) => SoP f c -> SoP f c Source #

simplifySoP :: (Ord f, Ord c) => SoP f c -> SoP f c Source #

mergeSoPAdd :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c Source #

mergeSoPMul :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c Source #

mergeSoPSub :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c Source #

mergeSoPDiv :: (Ord f, Ord c) => SoP f c -> SoP f c -> (SoP f c, SoP f c) Source #