Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
SoPSat.SoP
Synopsis
- data Atom f c
- data Symbol f c
- data Product f c
- data SoP f c
- data SoPE f c = SoPE {}
- class (Ord f, Ord c) => ToSoP f c a where
- (|+|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c
- (|-|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c
- (|*|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c
- (|/|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> (SoP f c, SoP f c)
- (|^|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> SoP f c
- data OrdRel
- constants :: (Ord f, Ord c) => SoP f c -> Set c
- atoms :: (Ord f, Ord c) => SoP f c -> Set (Atom f c)
- int :: Integer -> SoP f c
- cons :: c -> SoP f c
- symbol :: Atom f c -> SoP f c
- func :: (Ord f, Ord c) => f -> [SoP f c] -> SoP f c
- isConst :: Atom f c -> Bool
- isFunction :: Atom f c -> Bool
SoP Types
Atomic part of a SoP
like constants and unknown functions
The most basic part used during reasoning: - Numbers - Atoms - Exponents
Instances
(Ord f, Ord c) => ToSoP f c (Symbol f c) Source # | |
(Show f, Show c) => Show (Symbol f c) Source # | |
(Eq c, Eq f) => Eq (Symbol f c) Source # | |
(Ord c, Ord f) => Ord (Symbol f c) Source # | |
Defined in SoPSat.Internal.SoP |
Product of symbols
Instances
(Ord f, Ord c) => ToSoP f c (Product f c) Source # | |
(Show f, Show c) => Show (Product f c) Source # | |
(Eq f, Eq c) => Eq (Product f c) Source # | |
(Ord f, Ord c) => Ord (Product f c) Source # | |
Defined in SoPSat.Internal.SoP |
Sum of Products
Expression
Constructors
SoPE | |
class (Ord f, Ord c) => ToSoP f c a where Source #
Convertable to a sum of products
with f
being type to represent functions
and c
being type to represent constants
Operators
(|/|) :: (Ord f, Ord c) => SoP f c -> SoP f c -> (SoP f c, SoP f c) infixl 7 Source #
Division of SoP
s
Produces a tuple of a quotient and a remainder NB. Not implemented
Relations
Order relationship
Constructors
LeR | Less than or equal relationship |
EqR | Equality relationship |
GeR | Greater than or equal relationship |
Related
constants :: (Ord f, Ord c) => SoP f c -> Set c Source #
Collects constants used in SoP
Almost equivalent to
Data.Set.filter isConst . atoms
, but also collects constants used in functions
Predicates
isFunction :: Atom f c -> Bool Source #
Predicate for function Atom
s