mixed-types-num-0.3.1.1: 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.Ring

Contents

Description

 

Synopsis

Ring

type CanAddSubMulBy t s = (CanAddThis t s, CanSubThis t s, CanSub s t, SubType s t ~ t, CanMulBy t s) Source #

class (RingPre t, CanEnsureCN t, RingPre (EnsureCN t)) => Ring t Source #

Multiplication

type CanMul t1 t2 = (CanMulAsymmetric t1 t2, CanMulAsymmetric t2 t1, MulType t1 t2 ~ MulType t2 t1) Source #

class CanMulAsymmetric t1 t2 where Source #

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

Associated Types

type MulType t1 t2 Source #

Methods

mul :: t1 -> t2 -> MulType t1 t2 Source #

mul :: (MulType t1 t2 ~ t1, t1 ~ t2, Num t1) => t1 -> t2 -> MulType t1 t2 Source #

Instances

CanMulAsymmetric Double Double Source # 

Associated Types

type MulType Double Double :: * Source #

CanMulAsymmetric Double Int Source # 

Associated Types

type MulType Double Int :: * Source #

CanMulAsymmetric Double Integer Source # 

Associated Types

type MulType Double Integer :: * Source #

CanMulAsymmetric Double Rational Source # 

Associated Types

type MulType Double Rational :: * Source #

CanMulAsymmetric Int Double Source # 

Associated Types

type MulType Int Double :: * Source #

CanMulAsymmetric Int Int Source # 

Associated Types

type MulType Int Int :: * Source #

Methods

mul :: Int -> Int -> MulType Int Int Source #

CanMulAsymmetric Int Integer Source # 

Associated Types

type MulType Int Integer :: * Source #

CanMulAsymmetric Int Rational Source # 

Associated Types

type MulType Int Rational :: * Source #

CanMulAsymmetric Integer Double Source # 

Associated Types

type MulType Integer Double :: * Source #

CanMulAsymmetric Integer Int Source # 

Associated Types

type MulType Integer Int :: * Source #

CanMulAsymmetric Integer Integer Source # 

Associated Types

type MulType Integer Integer :: * Source #

CanMulAsymmetric Integer Rational Source # 

Associated Types

type MulType Integer Rational :: * Source #

CanMulAsymmetric Rational Double Source # 

Associated Types

type MulType Rational Double :: * Source #

CanMulAsymmetric Rational Int Source # 

Associated Types

type MulType Rational Int :: * Source #

CanMulAsymmetric Rational Integer Source # 

Associated Types

type MulType Rational Integer :: * Source #

CanMulAsymmetric Rational Rational Source # 
(CanMulAsymmetric Double b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MulType Double b0), SuitableForCE es0) => CanMulAsymmetric Double (CollectErrors es0 b0) Source # 

Associated Types

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

Methods

mul :: Double -> CollectErrors es0 b0 -> MulType Double (CollectErrors es0 b0) Source #

(CanMulAsymmetric Int b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MulType Int b0), SuitableForCE es0) => CanMulAsymmetric Int (CollectErrors es0 b0) Source # 

Associated Types

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

Methods

mul :: Int -> CollectErrors es0 b0 -> MulType Int (CollectErrors es0 b0) Source #

(CanMulAsymmetric Integer b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MulType Integer b0), SuitableForCE es0) => CanMulAsymmetric Integer (CollectErrors es0 b0) Source # 

Associated Types

type MulType Integer (CollectErrors es0 b0) :: * Source #

Methods

mul :: Integer -> CollectErrors es0 b0 -> MulType Integer (CollectErrors es0 b0) Source #

(CanMulAsymmetric Rational b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MulType Rational b0), SuitableForCE es0) => CanMulAsymmetric Rational (CollectErrors es0 b0) Source # 

Associated Types

type MulType Rational (CollectErrors es0 b0) :: * Source #

CanMulAsymmetric a b => CanMulAsymmetric [a] [b] Source # 

Associated Types

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

Methods

mul :: [a] -> [b] -> MulType [a] [b] Source #

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

Associated Types

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

Methods

mul :: Maybe a -> Maybe b -> MulType (Maybe a) (Maybe b) Source #

(CanMulAsymmetric a0 Double, CanEnsureCE es0 a0, CanEnsureCE es0 (MulType a0 Double), SuitableForCE es0) => CanMulAsymmetric (CollectErrors es0 a0) Double Source # 

Associated Types

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

Methods

mul :: CollectErrors es0 a0 -> Double -> MulType (CollectErrors es0 a0) Double Source #

(CanMulAsymmetric a0 Rational, CanEnsureCE es0 a0, CanEnsureCE es0 (MulType a0 Rational), SuitableForCE es0) => CanMulAsymmetric (CollectErrors es0 a0) Rational Source # 

Associated Types

type MulType (CollectErrors es0 a0) Rational :: * Source #

(CanMulAsymmetric a0 Int, CanEnsureCE es0 a0, CanEnsureCE es0 (MulType a0 Int), SuitableForCE es0) => CanMulAsymmetric (CollectErrors es0 a0) Int Source # 

Associated Types

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

Methods

mul :: CollectErrors es0 a0 -> Int -> MulType (CollectErrors es0 a0) Int Source #

(CanMulAsymmetric a0 Integer, CanEnsureCE es0 a0, CanEnsureCE es0 (MulType a0 Integer), SuitableForCE es0) => CanMulAsymmetric (CollectErrors es0 a0) Integer Source # 

Associated Types

type MulType (CollectErrors es0 a0) Integer :: * Source #

Methods

mul :: CollectErrors es0 a0 -> Integer -> MulType (CollectErrors es0 a0) Integer Source #

(CanMulAsymmetric a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (MulType a b), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) (CollectErrors es b) Source # 

Associated Types

type MulType (CollectErrors es a) (CollectErrors es b) :: * Source #

Methods

mul :: CollectErrors es a -> CollectErrors es b -> MulType (CollectErrors es a) (CollectErrors es b) Source #

type CanMulBy t1 t2 = (CanMul t1 t2, MulType t1 t2 ~ t1) Source #

(*) :: CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2 infixl 7 Source #

Tests

specCanMul :: (Show t1, Show t2, Show t3, Show (MulType t1 t2), Show (MulType t2 t1), Show (MulType t1 (MulType t2 t3)), Show (MulType (MulType t1 t2) t3), Show (MulType t1 (AddType t2 t3)), Show (AddType (MulType t1 t2) (MulType t1 t3)), Arbitrary t1, Arbitrary t2, Arbitrary t3, ConvertibleExactly Integer t2, CanTestCertainly (EqCompareType (MulType t1 t2) t1), CanTestCertainly (EqCompareType (MulType t1 t2) (MulType t2 t1)), CanTestCertainly (EqCompareType (MulType t1 (MulType t2 t3)) (MulType (MulType t1 t2) t3)), CanTestCertainly (EqCompareType (MulType t1 (AddType t2 t3)) (AddType (MulType t1 t2) (MulType t1 t3))), HasEqAsymmetric (MulType t1 t2) t1, HasEqAsymmetric (MulType t1 t2) (MulType t2 t1), HasEqAsymmetric (MulType t1 (MulType t2 t3)) (MulType (MulType t1 t2) t3), HasEqAsymmetric (MulType t1 (AddType t2 t3)) (AddType (MulType t1 t2) (MulType t1 t3)), CanAddAsymmetric t2 t3, CanAddAsymmetric (MulType t1 t2) (MulType t1 t3), CanMulAsymmetric t1 t2, CanMulAsymmetric t1 t3, CanMulAsymmetric t1 (MulType t2 t3), CanMulAsymmetric t1 (AddType t2 t3), CanMulAsymmetric t2 t1, CanMulAsymmetric t2 t3, CanMulAsymmetric (MulType t1 t2) t3) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanMul should satisfy.

specCanMulSameType :: (Show t, ConvertibleExactly Integer t, CanTestCertainly (EqCompareType t t), HasEqAsymmetric t t, CanMulAsymmetric t t, MulType t t ~ t) => T t -> Spec Source #

HSpec properties that each implementation of CanMulSameType should satisfy.

Exponentiation

class CanPow b e where Source #

A replacement for Prelude's binary ^ and ^^. If Num t1 and Integral t2, then one can use the default implementation to mirror Prelude's ^.

Minimal complete definition

powNoCN

Associated Types

type PowTypeNoCN b e Source #

type PowType b e Source #

Instances

CanPow Double Int Source # 
CanPow Double Integer Source # 
CanPow Int Int Source # 

Associated Types

type PowTypeNoCN Int Int :: * Source #

type PowType Int Int :: * Source #

CanPow Int Integer Source # 
CanPow Integer Int Source # 
CanPow Integer Integer Source # 
CanPow Rational Int Source # 
CanPow Rational Integer Source # 
(CanPow Double b0, CanEnsureCE es0 b0, CanEnsureCE es0 (PowType Double b0), CanEnsureCE es0 (PowTypeNoCN Double b0), SuitableForCE es0) => CanPow Double (CollectErrors es0 b0) Source # 

Associated Types

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

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

(CanPow Int b0, CanEnsureCE es0 b0, CanEnsureCE es0 (PowType Int b0), CanEnsureCE es0 (PowTypeNoCN Int b0), SuitableForCE es0) => CanPow Int (CollectErrors es0 b0) Source # 

Associated Types

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

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

Methods

powNoCN :: Int -> CollectErrors es0 b0 -> PowTypeNoCN Int (CollectErrors es0 b0) Source #

pow :: Int -> CollectErrors es0 b0 -> PowType Int (CollectErrors es0 b0) Source #

(CanPow Integer b0, CanEnsureCE es0 b0, CanEnsureCE es0 (PowType Integer b0), CanEnsureCE es0 (PowTypeNoCN Integer b0), SuitableForCE es0) => CanPow Integer (CollectErrors es0 b0) Source # 

Associated Types

type PowTypeNoCN Integer (CollectErrors es0 b0) :: * Source #

type PowType Integer (CollectErrors es0 b0) :: * Source #

(CanPow Rational b0, CanEnsureCE es0 b0, CanEnsureCE es0 (PowType Rational b0), CanEnsureCE es0 (PowTypeNoCN Rational b0), SuitableForCE es0) => CanPow Rational (CollectErrors es0 b0) Source # 
CanPow a b => CanPow (Maybe a) (Maybe b) Source # 

Associated Types

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

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

Methods

powNoCN :: Maybe a -> Maybe b -> PowTypeNoCN (Maybe a) (Maybe b) Source #

pow :: Maybe a -> Maybe b -> PowType (Maybe a) (Maybe b) Source #

(CanPow a0 Double, CanEnsureCE es0 a0, CanEnsureCE es0 (PowType a0 Double), CanEnsureCE es0 (PowTypeNoCN a0 Double), SuitableForCE es0) => CanPow (CollectErrors es0 a0) Double Source # 

Associated Types

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

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

(CanPow a0 Rational, CanEnsureCE es0 a0, CanEnsureCE es0 (PowType a0 Rational), CanEnsureCE es0 (PowTypeNoCN a0 Rational), SuitableForCE es0) => CanPow (CollectErrors es0 a0) Rational Source # 
(CanPow a0 Int, CanEnsureCE es0 a0, CanEnsureCE es0 (PowType a0 Int), CanEnsureCE es0 (PowTypeNoCN a0 Int), SuitableForCE es0) => CanPow (CollectErrors es0 a0) Int Source # 

Associated Types

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

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

Methods

powNoCN :: CollectErrors es0 a0 -> Int -> PowTypeNoCN (CollectErrors es0 a0) Int Source #

pow :: CollectErrors es0 a0 -> Int -> PowType (CollectErrors es0 a0) Int Source #

(CanPow a0 Integer, CanEnsureCE es0 a0, CanEnsureCE es0 (PowType a0 Integer), CanEnsureCE es0 (PowTypeNoCN a0 Integer), SuitableForCE es0) => CanPow (CollectErrors es0 a0) Integer Source # 

Associated Types

type PowTypeNoCN (CollectErrors es0 a0) Integer :: * Source #

type PowType (CollectErrors es0 a0) Integer :: * Source #

(CanPow a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (PowTypeNoCN a b), CanEnsureCE es (PowType a b), SuitableForCE es) => CanPow (CollectErrors es a) (CollectErrors es b) Source # 

Associated Types

type PowTypeNoCN (CollectErrors es a) (CollectErrors es b) :: * Source #

type PowType (CollectErrors es a) (CollectErrors es b) :: * Source #

type CanPowBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ t1, PowTypeNoCN t1 t2 ~ t1) Source #

type CanPowCNBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ EnsureCN t1, PowTypeNoCN t1 t2 ~ t1, CanEnsureCN t1, CanPow (EnsureCN t1) t2, PowType (EnsureCN t1) t2 ~ EnsureCN t1, PowTypeNoCN (EnsureCN t1) t2 ~ EnsureCN t1) Source #

(^) :: CanPow t1 t2 => t1 -> t2 -> PowType t1 t2 infixl 8 Source #

(^!) :: CanPow t1 t2 => t1 -> t2 -> PowTypeNoCN t1 t2 infixl 8 Source #

Like ^ but throwing an exception if the power is undefined.

powUsingMul :: (CanBeInteger e, CanMulSameType t) => t -> t -> e -> t Source #

Tests

specCanPow :: (Show t1, Show t2, Show (PowType t1 t2), Show (MulType t1 (PowType t1 t2)), Show (PowType t1 (AddType t2 Integer)), Arbitrary t1, Arbitrary t2, ConvertibleExactly Integer t1, ConvertibleExactly Integer t2, CanTestCertainly (EqCompareType (PowType t1 t2) t1), CanTestCertainly (EqCompareType (MulType t1 (PowType t1 t2)) (PowType t1 (AddType t2 Integer))), HasEqAsymmetric (PowType t1 t2) t1, HasEqAsymmetric (MulType t1 (PowType t1 t2)) (PowType t1 (AddType t2 Integer)), CanTestPosNeg t2, CanAddAsymmetric t2 Integer, CanPow t1 t2, CanPow t1 (AddType t2 Integer), CanMulAsymmetric t1 (PowType t1 t2)) => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanPow should satisfy.