Copyright | (C) 2017-18 Jakub Daniel |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Jakub Daniel <jakub.daniel@protonmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data ArithmeticF a (s :: Sort) where
- Const :: Int -> ArithmeticF a IntegralSort
- Add :: [a IntegralSort] -> ArithmeticF a IntegralSort
- Mul :: [a IntegralSort] -> ArithmeticF a IntegralSort
- Divides :: Int -> a IntegralSort -> ArithmeticF a BooleanSort
- LessThan :: a IntegralSort -> a IntegralSort -> ArithmeticF a BooleanSort
- cnst :: ArithmeticF :<: f => Int -> IFix f IntegralSort
- cnsts :: forall f (s :: Sort). (ArithmeticF :<: f, IFoldable f, IFunctor f, IEq1 f) => IFix f s -> [IFix f IntegralSort]
- add :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort
- mul :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort
- (.+.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort
- (.*.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort
- (.\.) :: ArithmeticF :<: f => Int -> IFix f IntegralSort -> IFix f BooleanSort
- (.<.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort
- (.>.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort
- (.<=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort
- (.>=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort
Documentation
data ArithmeticF a (s :: Sort) where Source #
A functor representing linear integer arithmetic: constants (cnst
), addition (add
or .+.
), multiplication (mul
or .*.
), divisibility predicate (.\.
) and ordering (.<.
, .>.
, .<=.
, .>=.
).
Const :: Int -> ArithmeticF a IntegralSort | |
Add :: [a IntegralSort] -> ArithmeticF a IntegralSort | |
Mul :: [a IntegralSort] -> ArithmeticF a IntegralSort | |
Divides :: Int -> a IntegralSort -> ArithmeticF a BooleanSort | |
LessThan :: a IntegralSort -> a IntegralSort -> ArithmeticF a BooleanSort |
Instances
cnst :: ArithmeticF :<: f => Int -> IFix f IntegralSort Source #
A smart constructor for integer constants
cnsts :: forall f (s :: Sort). (ArithmeticF :<: f, IFoldable f, IFunctor f, IEq1 f) => IFix f s -> [IFix f IntegralSort] Source #
Collects a list of all constants occurring in an expression.
add :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort Source #
A smart constructor for a variadic addition
mul :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort Source #
A smart constructor for a variadic multiplication
(.+.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort infixl 8 Source #
A smart constructor for binary addition
(.*.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort infixl 9 Source #
A smart constructor for a binary multiplication
(.\.) :: ArithmeticF :<: f => Int -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #
A smart constructor for a divisibility predicate
(.<.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #
A smart constructor for <
(.>.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #
A smart constructor for >
(.<=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #
A smart constructor for <=
(.>=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #
A smart constructor for >=