mixed-types-num-0.3.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

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), DivType t1 t2 ~ EnsureCN (DivTypeNoCN t1 t2)) => t1 -> t2 -> DivType t1 t2 Source #

Instances
CanDiv Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Double Int :: Type Source #

type DivType Double Int :: Type Source #

CanDiv Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Int Double :: Type Source #

type DivType Int Double :: Type Source #

CanDiv Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Int Int :: Type Source #

type DivType Int Int :: Type Source #

CanDiv Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Int Integer :: Type Source #

type DivType Int Integer :: Type Source #

CanDiv Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Int Rational :: Type Source #

type DivType Int Rational :: Type Source #

CanDiv Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Integer Int :: Type Source #

type DivType Integer Int :: Type Source #

CanDiv Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Rational Int :: Type Source #

type DivType Rational Int :: Type Source #

CanDiv Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Field

CanDiv Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Field

(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 DivTypeNoCN Double (Complex b) :: Type Source #

type DivType Double (Complex b) :: Type 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 DivTypeNoCN Int (Complex b) :: Type Source #

type DivType Int (Complex b) :: Type 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 DivTypeNoCN Integer (Complex b) :: Type Source #

type DivType Integer (Complex b) :: Type 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 DivTypeNoCN Rational (Complex b) :: Type Source #

type DivType Rational (Complex b) :: Type Source #

(CanDiv Double b, CanEnsureCE es b, CanEnsureCE es (DivType Double b), CanEnsureCE es (DivTypeNoCN Double b), SuitableForCE es) => CanDiv Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Double (CollectErrors es b) :: Type Source #

type DivType Double (CollectErrors es b) :: Type Source #

(CanDiv Int b, CanEnsureCE es b, CanEnsureCE es (DivType Int b), CanEnsureCE es (DivTypeNoCN Int b), SuitableForCE es) => CanDiv Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Int (CollectErrors es b) :: Type Source #

type DivType Int (CollectErrors es b) :: Type Source #

(CanDiv Integer b, CanEnsureCE es b, CanEnsureCE es (DivType Integer b), CanEnsureCE es (DivTypeNoCN Integer b), SuitableForCE es) => CanDiv Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Integer (CollectErrors es b) :: Type Source #

type DivType Integer (CollectErrors es b) :: Type Source #

(CanDiv Rational b, CanEnsureCE es b, CanEnsureCE es (DivType Rational b), CanEnsureCE es (DivTypeNoCN Rational b), SuitableForCE es) => CanDiv Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN Rational (CollectErrors es b) :: Type Source #

type DivType Rational (CollectErrors es b) :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivTypeNoCN (Complex a) Integer :: Type Source #

type DivType (Complex a) Integer :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivTypeNoCN (Complex a) Int :: Type Source #

type DivType (Complex a) Int :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivTypeNoCN (Complex a) Rational :: Type Source #

type DivType (Complex a) Rational :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type DivTypeNoCN (Complex a) Double :: Type Source #

type DivType (Complex a) Double :: Type Source #

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

Defined in Numeric.MixedTypes.Field

Associated Types

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

type DivType [a] [b] :: Type 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 # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

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

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

Methods

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

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 DivTypeNoCN (Complex a) (Complex b) :: Type Source #

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

(CanDiv a Integer, CanEnsureCE es a, CanEnsureCE es (DivType a Integer), CanEnsureCE es (DivTypeNoCN a Integer), SuitableForCE es) => CanDiv (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN (CollectErrors es a) Integer :: Type Source #

type DivType (CollectErrors es a) Integer :: Type Source #

(CanDiv a Int, CanEnsureCE es a, CanEnsureCE es (DivType a Int), CanEnsureCE es (DivTypeNoCN a Int), SuitableForCE es) => CanDiv (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN (CollectErrors es a) Int :: Type Source #

type DivType (CollectErrors es a) Int :: Type Source #

(CanDiv a Rational, CanEnsureCE es a, CanEnsureCE es (DivType a Rational), CanEnsureCE es (DivTypeNoCN a Rational), SuitableForCE es) => CanDiv (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN (CollectErrors es a) Rational :: Type Source #

type DivType (CollectErrors es a) Rational :: Type Source #

(CanDiv a Double, CanEnsureCE es a, CanEnsureCE es (DivType a Double), CanEnsureCE es (DivTypeNoCN a Double), SuitableForCE es) => CanDiv (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN (CollectErrors es a) Double :: Type Source #

type DivType (CollectErrors es a) Double :: Type Source #

(CanDiv a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (DivType a b), CanEnsureCE es (DivTypeNoCN a b), SuitableForCE es) => CanDiv (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Field

Associated Types

type DivTypeNoCN (CollectErrors es a) (CollectErrors es b) :: Type Source #

type DivType (CollectErrors es a) (CollectErrors es b) :: Type Source #

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

type CanDivCNBy t1 t2 = (CanDiv t1 t2, DivType t1 t2 ~ EnsureCN t1, DivTypeNoCN t1 t2 ~ t1, CanEnsureCN t1, CanDiv (EnsureCN t1) t2, DivType (EnsureCN t1) t2 ~ EnsureCN t1, DivTypeNoCN (EnsureCN 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