mixed-types-num-0.2: Alternative Prelude with numeric and logic expressions typed bottom-up

Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Numeric.MixedTypes.Field

Contents

Description

 

Synopsis

Field

type Field t = (FieldPre t, CanEnsureCN t, FieldPre (EnsureCN t)) Source #

type CertainlyEqField t = (CertainlyEqFieldPre t, CanEnsureCN t, CertainlyEqFieldPre (EnsureCN t)) Source #

type OrderedField t = (OrderedFieldPre t, CanEnsureCN t, OrderedFieldPre (EnsureCN t)) Source #

type OrderedCertainlyField t = (OrderedCertainlyFieldPre t, CanEnsureCN t, OrderedCertainlyFieldPre (EnsureCN t)) Source #

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 /.

Minimal complete definition

divideNoCN

Associated Types

type DivTypeNoCN t1 t2 Source #

type DivType t1 t2 Source #

Methods

divideNoCN :: t1 -> t2 -> DivTypeNoCN t1 t2 Source #

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

divide :: (CanTestZero t2, CanEnsureCN (DivTypeNoCN t1 t2)) => t1 -> t2 -> EnsureCN (DivTypeNoCN t1 t2) Source #

Instances

CanDiv Double Double Source # 
CanDiv Double Int Source # 
CanDiv Double Integer Source # 
CanDiv Double Rational Source # 
CanDiv Int Double Source # 
CanDiv Int Int Source # 

Associated Types

type DivTypeNoCN Int Int :: * Source #

type DivType Int Int :: * Source #

CanDiv Int Integer Source # 
CanDiv Int Rational Source # 
CanDiv Integer Double Source # 
CanDiv Integer Int Source # 
CanDiv Integer Integer Source # 
CanDiv Integer Rational Source # 
CanDiv Rational Double Source # 
CanDiv Rational Int Source # 
CanDiv Rational Integer Source # 
CanDiv Rational Rational Source # 
(CanDiv Double b0, CanEnsureCE es0 (DivType Double b0), CanEnsureCE es0 (DivTypeNoCN Double b0), SuitableForCE es0) => CanDiv Double (CollectErrors es0 b0) Source # 

Associated Types

type DivTypeNoCN Double (CollectErrors es0 b0) :: * Source #

type DivType Double (CollectErrors es0 b0) :: * Source #

(CanDiv Int b0, CanEnsureCE es0 (DivType Int b0), CanEnsureCE es0 (DivTypeNoCN Int b0), SuitableForCE es0) => CanDiv Int (CollectErrors es0 b0) Source # 

Associated Types

type DivTypeNoCN Int (CollectErrors es0 b0) :: * Source #

type DivType Int (CollectErrors es0 b0) :: * Source #

(CanDiv Integer b0, CanEnsureCE es0 (DivType Integer b0), CanEnsureCE es0 (DivTypeNoCN Integer b0), SuitableForCE es0) => CanDiv Integer (CollectErrors es0 b0) Source # 
(CanDiv Rational b0, CanEnsureCE es0 (DivType Rational b0), CanEnsureCE es0 (DivTypeNoCN Rational b0), SuitableForCE es0) => CanDiv Rational (CollectErrors es0 b0) Source # 
CanDiv a b => CanDiv [a] [b] Source # 

Associated Types

type DivTypeNoCN [a] [b] :: * Source #

type DivType [a] [b] :: * Source #

Methods

divideNoCN :: [a] -> [b] -> DivTypeNoCN [a] [b] Source #

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

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

Associated Types

type DivTypeNoCN (Maybe a) (Maybe b) :: * Source #

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

Methods

divideNoCN :: Maybe a -> Maybe b -> DivTypeNoCN (Maybe a) (Maybe b) Source #

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

(CanDiv a0 Double, CanEnsureCE es0 (DivType a0 Double), CanEnsureCE es0 (DivTypeNoCN a0 Double), SuitableForCE es0) => CanDiv (CollectErrors es0 a0) Double Source # 

Associated Types

type DivTypeNoCN (CollectErrors es0 a0) Double :: * Source #

type DivType (CollectErrors es0 a0) Double :: * Source #

(CanDiv a0 Rational, CanEnsureCE es0 (DivType a0 Rational), CanEnsureCE es0 (DivTypeNoCN a0 Rational), SuitableForCE es0) => CanDiv (CollectErrors es0 a0) Rational Source # 
(CanDiv a0 Int, CanEnsureCE es0 (DivType a0 Int), CanEnsureCE es0 (DivTypeNoCN a0 Int), SuitableForCE es0) => CanDiv (CollectErrors es0 a0) Int Source # 

Associated Types

type DivTypeNoCN (CollectErrors es0 a0) Int :: * Source #

type DivType (CollectErrors es0 a0) Int :: * Source #

(CanDiv a0 Integer, CanEnsureCE es0 (DivType a0 Integer), CanEnsureCE es0 (DivTypeNoCN a0 Integer), SuitableForCE es0) => CanDiv (CollectErrors es0 a0) Integer Source # 
(CanDiv a b, CanEnsureCE es (DivType a b), CanEnsureCE es (DivTypeNoCN a b), SuitableForCE es) => CanDiv (CollectErrors es a) (CollectErrors es b) Source # 

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

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

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

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

Tests

specCanDiv :: (CanRecip t1, CanRecip (DivType Integer t1), Show (DivType Integer (DivType Integer t1)), HasEqCertainly t1 (DivType Integer (DivType Integer t1)), CanTestZero (DivType Integer t1), CanDivX t1 t2, CanTestZero t1, CanTestZero t2, CanDivX t1 t1, CanMulX t1 (DivType t1 t2), ConvertibleExactly Integer t2, ConvertibleExactly Integer t1) => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanDiv should satisfy.

specCanDivNotMixed :: (CanRecip t, CanRecip (DivType Integer t), Show (DivType Integer (DivType Integer t)), HasEqCertainly t (DivType Integer (DivType Integer t)), CanTestZero (DivType Integer t), CanDivX t t, CanTestZero t, CanMulX t (DivType t t), ConvertibleExactly Integer t) => T t -> Spec Source #

HSpec properties that each implementation of CanDiv should satisfy.

type CanDivX t1 t2 = (CanDiv t1 t2, Show t1, Arbitrary t1, Show t2, Arbitrary t2, Show (DivType t1 t2), HasEqCertainly t1 (DivType t1 t2)) Source #

Compound type constraint useful for test definition.