mixed-types-num-0.5.9.1: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.MixedTypes.Div

Description

 
Synopsis

Division

class CanDiv t1 t2 where Source #

A replacement for Prelude's binary /. If t1 = t2 and Fractional t1, then one can use the default implementation to mirror Prelude's /.

Associated Types

type DivType t1 t2 Source #

type DivType t1 t2 = t1

Methods

divide :: t1 -> t2 -> DivType t1 t2 Source #

Instances

Instances details
CanDiv Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Double Double Source #

CanDiv Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Double Int Source #

CanDiv Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Double Integer Source #

CanDiv Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Double Rational Source #

CanDiv Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Int Double Source #

CanDiv Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Int Int Source #

Methods

divide :: Int -> Int -> DivType Int Int Source #

CanDiv Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Int Integer Source #

CanDiv Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Int Rational Source #

CanDiv Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Integer Double Source #

CanDiv Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Integer Int Source #

CanDiv Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Integer Integer Source #

CanDiv Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Integer Rational Source #

CanDiv Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Rational Double Source #

CanDiv Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Rational Int Source #

CanDiv Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Rational Integer Source #

CanDiv Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Rational Rational Source #

(CanMulAsymmetric Double b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Double b) (MulType b b)) => CanDiv Double (Complex b) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType Double (Complex b) Source #

(CanDiv Double b, CanTestZero b) => CanDiv Double (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Double (CN b) Source #

Methods

divide :: Double -> CN b -> DivType Double (CN b) Source #

(CanMulAsymmetric Int b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Int b) (MulType b b)) => CanDiv Int (Complex b) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType Int (Complex b) Source #

Methods

divide :: Int -> Complex b -> DivType Int (Complex b) Source #

(CanDiv Int b, CanTestZero b) => CanDiv Int (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Int (CN b) Source #

Methods

divide :: Int -> CN b -> DivType Int (CN b) Source #

(CanMulAsymmetric Integer b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Integer b) (MulType b b)) => CanDiv Integer (Complex b) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType Integer (Complex b) Source #

(CanDiv Integer b, CanTestZero b) => CanDiv Integer (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Integer (CN b) Source #

Methods

divide :: Integer -> CN b -> DivType Integer (CN b) Source #

(CanMulAsymmetric Rational b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Rational b) (MulType b b)) => CanDiv Rational (Complex b) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType Rational (Complex b) Source #

(CanDiv Rational b, CanTestZero b) => CanDiv Rational (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType Rational (CN b) Source #

Methods

divide :: Rational -> CN b -> DivType Rational (CN b) Source #

CanDiv a Integer => CanDiv (Complex a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType (Complex a) Integer Source #

CanDiv a Int => CanDiv (Complex a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType (Complex a) Int Source #

Methods

divide :: Complex a -> Int -> DivType (Complex a) Int Source #

CanDiv a Rational => CanDiv (Complex a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType (Complex a) Rational Source #

CanDiv a Double => CanDiv (Complex a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType (Complex a) Double Source #

CanDiv a Integer => CanDiv (CN a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (CN a) Integer Source #

Methods

divide :: CN a -> Integer -> DivType (CN a) Integer Source #

CanDiv a Int => CanDiv (CN a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (CN a) Int Source #

Methods

divide :: CN a -> Int -> DivType (CN a) Int Source #

CanDiv a Rational => CanDiv (CN a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (CN a) Rational Source #

Methods

divide :: CN a -> Rational -> DivType (CN a) Rational Source #

CanDiv a Double => CanDiv (CN a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (CN a) Double Source #

Methods

divide :: CN a -> Double -> DivType (CN a) Double Source #

CanDiv a b => CanDiv [a] [b] Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType [a] [b] Source #

Methods

divide :: [a] -> [b] -> DivType [a] [b] Source #

CanDiv a b => CanDiv (Maybe a) (Maybe b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (Maybe a) (Maybe b) Source #

Methods

divide :: Maybe a -> Maybe b -> DivType (Maybe a) (Maybe b) Source #

(CanMulAsymmetric a b, CanAddSameType (MulType a b), CanSubSameType (MulType a b), CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType a b) (MulType b b)) => CanDiv (Complex a) (Complex b) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivType (Complex a) (Complex b) Source #

Methods

divide :: Complex a -> Complex b -> DivType (Complex a) (Complex b) Source #

(CanDiv a b, CanTestZero b) => CanDiv (CN a) (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Div

Associated Types

type DivType (CN a) (CN b) Source #

Methods

divide :: CN a -> CN b -> DivType (CN a) (CN b) Source #

type CanDivBy t1 t2 = (CanDiv t1 t2, DivType t1 t2 ~ t1) Source #

(/) :: CanDiv t1 t2 => t1 -> t2 -> DivType t1 t2 infixl 7 Source #

Tests

specCanDiv :: _ => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanDiv should satisfy.

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

HSpec properties that each implementation of CanDiv should satisfy.