Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data EpsFold i
- eps :: i -> EpsFold i
- mkEpsFold :: Ord i => [i] -> EpsFold i
- hasNoPertubation :: EpsFold i -> Bool
- factors :: EpsFold i -> Bag i
- suitableBase :: EpsFold i -> Int
- data Term i r = Term r (EpsFold i)
- term :: r -> i -> Term i r
- constantFactor :: Lens' (Term i r) r
- data Symbolic i r
- constant :: Ord i => r -> Symbolic i r
- symbolic :: Ord i => r -> i -> Symbolic i r
- perturb :: (Num r, Ord i) => r -> i -> Symbolic i r
- toTerms :: Symbolic i r -> [Term i r]
- signOf :: (Num r, Eq r) => Symbolic i r -> Maybe Sign
Documentation
hasNoPertubation :: EpsFold i -> Bool Source #
Test if the epsfold has no pertubation at all (i.e. if it is \(\Pi_{\emptyset}\)
suitableBase :: EpsFold i -> Int Source #
computes a base d
that can be used as:
\( \varepsilon(i) = \varepsilon^{d^i} \)
A term 'Term c es' represents a term:
\[ c \Pi_{i \in es} \varepsilon(i) \]
for a constant c and an arbitrarily small value \(\varepsilon\), parameterized by i.
constantFactor :: Lens' (Term i r) r Source #
Lens to access the constant c
in the term.
Represents a Sum of terms, i.e. a value that has the form:
\[ \sum c \Pi_i \varepsilon(i) \]
The terms are represented in order of decreasing significance.
The main idea in this type is that, if symbolic values contains \(\varepsilon(i)\) terms we can always order them. That is, two Symbolic terms will be equal only if:
- they contain *only* a constant term (that is equal)
- they contain the exact same \(\varepsilon\)-fold.
Instances
Functor (Symbolic i) Source # | |
(Ord i, Eq r, Num r) => Eq (Symbolic i r) Source # | |
(Ord i, Num r, Eq r) => Num (Symbolic i r) Source # | |
Defined in Algorithms.Geometry.SoS.Symbolic (+) :: Symbolic i r -> Symbolic i r -> Symbolic i r # (-) :: Symbolic i r -> Symbolic i r -> Symbolic i r # (*) :: Symbolic i r -> Symbolic i r -> Symbolic i r # negate :: Symbolic i r -> Symbolic i r # abs :: Symbolic i r -> Symbolic i r # signum :: Symbolic i r -> Symbolic i r # fromInteger :: Integer -> Symbolic i r # | |
(Ord i, Ord r, Num r) => Ord (Symbolic i r) Source # | |
Defined in Algorithms.Geometry.SoS.Symbolic | |
(Show i, Show r) => Show (Symbolic i r) Source # | |
(Arbitrary r, Ord i, Arbitrary (EpsFold i)) => Arbitrary (Symbolic i r) Source # | |
symbolic :: Ord i => r -> i -> Symbolic i r Source #
Creates a symbolic vlaue with a single indexed term. If you just need a constant (i.e. non-indexed), use constant
perturb :: (Num r, Ord i) => r -> i -> Symbolic i r Source #
given the value c and the index i, creates the perturbed value \(c + \varepsilon(i)\)