Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Synopsis
- class CanDivIMod t1 t2 where
- type CanDivIModIntegerSameType t = (CanDivIMod t t, CanEnsureCN t, DivIType t t ~ CN Integer, ModType t t ~ EnsureCN t)
- modNoCN :: (CanDivIMod t1 t2, ModType t1 t2 ~ EnsureCN t1, CanEnsureCN t1) => t1 -> t2 -> t1
- divINoCN :: (CanDivIMod t1 t2, DivIType t1 t2 ~ CN Integer) => t1 -> t2 -> Integer
- divIModNoCN :: (CanDivIMod t1 t2, ModType t1 t2 ~ EnsureCN t1, CanEnsureCN t1, DivIType t1 t2 ~ CN Integer) => t1 -> t2 -> (Integer, t1)
- class CanRound t where
- class HasIntegerBounds t where
- integerBounds :: t -> (Integer, Integer)
- specCanDivIMod :: (CanDivIModX t, HasIntegers t) => T t -> Spec
- specCanRound :: (CanRoundX t, HasIntegers t) => T t -> Spec
- specHasIntegerBounds :: HasIntegerBoundsX t => T t -> Spec
Rounded division + modulus
class CanDivIMod t1 t2 where Source #
divIMod :: t1 -> t2 -> (DivIType t1 t2, ModType t1 t2) Source #
Instances
CanDivIMod Double Double Source # | |
Defined in Numeric.MixedTypes.Round | |
CanDivIMod Double Integer Source # | |
Defined in Numeric.MixedTypes.Round | |
CanDivIMod Integer Integer Source # | |
Defined in Numeric.MixedTypes.Round | |
CanDivIMod Rational Integer Source # | |
Defined in Numeric.MixedTypes.Round | |
CanDivIMod Rational Rational Source # | |
Defined in Numeric.MixedTypes.Round |
type CanDivIModIntegerSameType t = (CanDivIMod t t, CanEnsureCN t, DivIType t t ~ CN Integer, ModType t t ~ EnsureCN t) Source #
modNoCN :: (CanDivIMod t1 t2, ModType t1 t2 ~ EnsureCN t1, CanEnsureCN t1) => t1 -> t2 -> t1 Source #
divIModNoCN :: (CanDivIMod t1 t2, ModType t1 t2 ~ EnsureCN t1, CanEnsureCN t1, DivIType t1 t2 ~ CN Integer) => t1 -> t2 -> (Integer, t1) Source #
Rounding
class CanRound t where Source #
A replacement for Prelude's RealFrac
operations, such as round in
which the result type is fixed to Integer.
If RealFrac t
and CanTestPosNeg t
,
then one can use the default implementation to mirror Prelude's round
, etc.
In other cases, it is sufficient to define properFraction
.
Nothing
properFraction :: t -> (Integer, t) Source #
properFraction :: RealFrac t => t -> (Integer, t) Source #
truncate :: t -> Integer Source #
round :: t -> Integer Source #
round :: HasOrderCertainly t Rational => t -> Integer Source #
ceiling :: t -> Integer Source #
ceiling :: CanTestPosNeg t => t -> Integer Source #
floor :: t -> Integer Source #
floor :: CanTestPosNeg t => t -> Integer Source #
class HasIntegerBounds t where Source #
Nothing
integerBounds :: t -> (Integer, Integer) Source #
integerBounds :: CanRound t => t -> (Integer, Integer) Source #
Instances
HasIntegerBounds Double Source # | |
Defined in Numeric.MixedTypes.Round | |
HasIntegerBounds Int Source # | |
Defined in Numeric.MixedTypes.Round | |
HasIntegerBounds Integer Source # | |
Defined in Numeric.MixedTypes.Round | |
HasIntegerBounds Rational Source # | |
Defined in Numeric.MixedTypes.Round |
Tests
specCanDivIMod :: (CanDivIModX t, HasIntegers t) => T t -> Spec Source #
HSpec properties that each implementation of CanRound should satisfy.
specCanRound :: (CanRoundX t, HasIntegers t) => T t -> Spec Source #
HSpec properties that each implementation of CanRound should satisfy.
specHasIntegerBounds :: HasIntegerBoundsX t => T t -> Spec Source #
HSpec properties that each implementation of CanRound should satisfy.