mixed-types-num-0.5.11: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny
LicenseBSD3
Maintainer[email protected]
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.MixedTypes.Round

Description

 
Synopsis

Rounded division + modulus

class CanDivIMod t1 t2 where Source #

Minimal complete definition

divIMod

Associated Types

type DivIType t1 t2 Source #

type ModType t1 t2 Source #

type ModType t1 t2 = t1

Methods

divIMod :: t1 -> t2 -> (DivIType t1 t2, ModType t1 t2) Source #

mod :: t1 -> t2 -> ModType t1 t2 Source #

divI :: t1 -> t2 -> DivIType t1 t2 Source #

Instances

Instances details
CanDivIMod Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Round

CanDivIMod Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Round

CanDivIMod Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Int Int Source #

type ModType Int Int Source #

CanDivIMod Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Int Integer Source #

type ModType Int Integer Source #

CanDivIMod Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Int Rational Source #

type ModType Int Rational Source #

CanDivIMod Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Integer Int Source #

type ModType Integer Int Source #

CanDivIMod Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Round

CanDivIMod Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Round

CanDivIMod Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Rational Int Source #

type ModType Rational Int Source #

CanDivIMod Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Round

CanDivIMod Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Round

(CanDivIMod Double t2, CanTestPosNeg t2) => CanDivIMod Double (CN t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Double (CN t2) Source #

type ModType Double (CN t2) Source #

Methods

divIMod :: Double -> CN t2 -> (DivIType Double (CN t2), ModType Double (CN t2)) Source #

mod :: Double -> CN t2 -> ModType Double (CN t2) Source #

divI :: Double -> CN t2 -> DivIType Double (CN t2) Source #

(CanDivIMod Int t2, CanTestPosNeg t2) => CanDivIMod Int (CN t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Int (CN t2) Source #

type ModType Int (CN t2) Source #

Methods

divIMod :: Int -> CN t2 -> (DivIType Int (CN t2), ModType Int (CN t2)) Source #

mod :: Int -> CN t2 -> ModType Int (CN t2) Source #

divI :: Int -> CN t2 -> DivIType Int (CN t2) Source #

(CanDivIMod Integer t2, CanTestPosNeg t2) => CanDivIMod Integer (CN t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Integer (CN t2) Source #

type ModType Integer (CN t2) Source #

Methods

divIMod :: Integer -> CN t2 -> (DivIType Integer (CN t2), ModType Integer (CN t2)) Source #

mod :: Integer -> CN t2 -> ModType Integer (CN t2) Source #

divI :: Integer -> CN t2 -> DivIType Integer (CN t2) Source #

(CanDivIMod Rational t2, CanTestPosNeg t2) => CanDivIMod Rational (CN t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType Rational (CN t2) Source #

type ModType Rational (CN t2) Source #

Methods

divIMod :: Rational -> CN t2 -> (DivIType Rational (CN t2), ModType Rational (CN t2)) Source #

mod :: Rational -> CN t2 -> ModType Rational (CN t2) Source #

divI :: Rational -> CN t2 -> DivIType Rational (CN t2) Source #

CanDivIMod t1 Integer => CanDivIMod (CN t1) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType (CN t1) Integer Source #

type ModType (CN t1) Integer Source #

Methods

divIMod :: CN t1 -> Integer -> (DivIType (CN t1) Integer, ModType (CN t1) Integer) Source #

mod :: CN t1 -> Integer -> ModType (CN t1) Integer Source #

divI :: CN t1 -> Integer -> DivIType (CN t1) Integer Source #

CanDivIMod t1 Int => CanDivIMod (CN t1) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType (CN t1) Int Source #

type ModType (CN t1) Int Source #

Methods

divIMod :: CN t1 -> Int -> (DivIType (CN t1) Int, ModType (CN t1) Int) Source #

mod :: CN t1 -> Int -> ModType (CN t1) Int Source #

divI :: CN t1 -> Int -> DivIType (CN t1) Int Source #

CanDivIMod t1 Rational => CanDivIMod (CN t1) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType (CN t1) Rational Source #

type ModType (CN t1) Rational Source #

Methods

divIMod :: CN t1 -> Rational -> (DivIType (CN t1) Rational, ModType (CN t1) Rational) Source #

mod :: CN t1 -> Rational -> ModType (CN t1) Rational Source #

divI :: CN t1 -> Rational -> DivIType (CN t1) Rational Source #

CanDivIMod t1 Double => CanDivIMod (CN t1) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType (CN t1) Double Source #

type ModType (CN t1) Double Source #

Methods

divIMod :: CN t1 -> Double -> (DivIType (CN t1) Double, ModType (CN t1) Double) Source #

mod :: CN t1 -> Double -> ModType (CN t1) Double Source #

divI :: CN t1 -> Double -> DivIType (CN t1) Double Source #

(CanDivIMod t1 t2, CanTestPosNeg t2) => CanDivIMod (CN t1) (CN t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Round

Associated Types

type DivIType (CN t1) (CN t2) Source #

type ModType (CN t1) (CN t2) Source #

Methods

divIMod :: CN t1 -> CN t2 -> (DivIType (CN t1) (CN t2), ModType (CN t1) (CN t2)) Source #

mod :: CN t1 -> CN t2 -> ModType (CN t1) (CN t2) Source #

divI :: CN t1 -> CN t2 -> DivIType (CN t1) (CN t2) 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.

Minimal complete definition

Nothing

Associated Types

type RoundType t Source #

Methods

properFraction :: t -> (RoundType t, t) Source #

default properFraction :: (RealFrac t, RoundType t ~ Integer) => t -> (RoundType t, t) Source #

truncate :: t -> RoundType t Source #

round :: t -> RoundType t Source #

ceiling :: t -> RoundType t Source #

default ceiling :: (CanTestPosNeg t, RoundType t ~ Integer) => t -> RoundType t Source #

floor :: t -> RoundType t Source #

default floor :: (CanTestPosNeg t, RoundType t ~ Integer) => t -> RoundType t Source #

class HasIntegerBounds t where Source #

Minimal complete definition

Nothing

Tests

specCanDivIMod :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanRound should satisfy.

specCanRound :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanRound should satisfy.

specHasIntegerBounds :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanRound should satisfy.