Safe Haskell | None |
---|---|
Language | Haskell2010 |
Representation of integers (Z) and reals (R) of similar precision. Programs are abstracted over this, so that ideally in the future we could have a solver that produces Integers and Rationals, instead of just Ints and Doubles.
We bundle Z and R up into a single representation instead of abstracting over both, because we must be able to convert from Z to R without loss.
Synopsis
- class (Num (Z c), Ord (Z c), Eq (Z c), Integral (Z c), Num (R c), Ord (R c), Eq (R c), RealFrac (R c)) => Rep c where
- data Assignment z r c = Assignment (Map z (Z c)) (Map r (R c))
- zOf :: (Rep c, Ord z) => Assignment z r c -> z -> Z c
- rOf :: (Rep c, Ord r) => Assignment z r c -> r -> R c
- zrOf :: (Rep c, Ord z, Ord r) => Assignment z r c -> Either z r -> R c
- assSize :: Assignment z r c -> Int
Documentation
class (Num (Z c), Ord (Z c), Eq (Z c), Integral (Z c), Num (R c), Ord (R c), Eq (R c), RealFrac (R c)) => Rep c where Source #
The Representation class. Requires its members Z c
and R c
to be Num
, Ord
and Eq
.
For some reason, for type inference to work, the members must be data
instead of type
.
This gives some minor annoyances when unpacking them. See unwrapR
below.
Nothing
Convert an integer to a real. This should not lose any precision.
(whereas fromIntegral 1000 :: Word8
would lose precision)
data Assignment z r c Source #
An assignment from variables to values. Maps integer variables to integers, and real variables to reals.
Assignment (Map z (Z c)) (Map r (R c)) |
Instances
(Show (Z c), Show (R c), Show z, Show r) => Show (Assignment z r c) Source # | |
Defined in Numeric.Limp.Rep.Rep showsPrec :: Int -> Assignment z r c -> ShowS # show :: Assignment z r c -> String # showList :: [Assignment z r c] -> ShowS # | |
(Ord z, Ord r) => Semigroup (Assignment z r c) Source # | |
Defined in Numeric.Limp.Rep.Rep (<>) :: Assignment z r c -> Assignment z r c -> Assignment z r c # sconcat :: NonEmpty (Assignment z r c) -> Assignment z r c # stimes :: Integral b => b -> Assignment z r c -> Assignment z r c # | |
(Ord z, Ord r) => Monoid (Assignment z r c) Source # | |
Defined in Numeric.Limp.Rep.Rep mempty :: Assignment z r c # mappend :: Assignment z r c -> Assignment z r c -> Assignment z r c # mconcat :: [Assignment z r c] -> Assignment z r c # |
zOf :: (Rep c, Ord z) => Assignment z r c -> z -> Z c Source #
Retrieve value of integer variable - or 0, if there is no value.
rOf :: (Rep c, Ord r) => Assignment z r c -> r -> R c Source #
Retrieve value of real variable - or 0, if there is no value.
zrOf :: (Rep c, Ord z, Ord r) => Assignment z r c -> Either z r -> R c Source #
Retrieve value of an integer or real variable, with result cast to a real regardless.
assSize :: Assignment z r c -> Int Source #