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

Contents

Description

 
Synopsis

Documentation

type IsBool t = (HasBools t, CanNegSameType t, CanAndOrSameType t) Source #

A type constraint synonym that stipulates that the type behaves very much like Bool, except it does not necessarily satisfy the law of excluded middle, which means that the type can contain a "do-not-know" value.

Examples: Bool, Maybe Bool, Maybe (Maybe Bool), CollectErrors Bool

specIsBool :: (IsBool t, CanTestCertainly t, Show t, Serial IO t) => T t -> Spec Source #

HSpec properties that each implementation of IsBool should satisfy.

Conversion to/from Bool

class HasBools t => CanTestCertainly t where Source #

Tests for truth or falsity. Beware, when isCertainlyTrue returns False, it does not mean that the proposition is false. It usually means that we failed to prove the proposition.

specCanTestCertainly :: CanTestCertainly t => T t -> Spec Source #

HSpec properties that each implementation of CanTestCertainly should satisfy.

type CanTestCertainlyX t = (CanTestCertainly t, Show t, Serial IO t) Source #

Compound type constraint useful for test definition.

stronglyImplies :: (CanTestCertainly t1, CanTestCertainly t2) => t1 -> t2 -> Bool Source #

If l is certainly True, then r is also certainly True.

weaklyImplies :: (CanTestCertainly t1, CanTestCertainly t2) => t1 -> t2 -> Bool Source #

If l is certainly True, then r is not certainly False.

Negation

class CanNeg t where Source #

This is negation is both the numeric negation as well as the Boolean negation. Example of non-standard Boolean negation:

 negate (Just True) = Just False
 

Associated Types

type NegType t Source #

Methods

negate :: t -> NegType t Source #

Instances
CanNeg Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type NegType Bool :: Type Source #

CanNeg Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type NegType Double :: Type Source #

CanNeg Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type NegType Int :: Type Source #

Methods

negate :: Int -> NegType Int Source #

CanNeg Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type NegType Integer :: Type Source #

CanNeg Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type NegType Rational :: Type Source #

CanNeg t => CanNeg (Maybe t) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type NegType (Maybe t) :: Type Source #

Methods

negate :: Maybe t -> NegType (Maybe t) Source #

CanNeg t => CanNeg (Complex t) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type NegType (Complex t) :: Type Source #

Methods

negate :: Complex t -> NegType (Complex t) Source #

(CanNeg t, SuitableForCE es, CanEnsureCE es t, CanEnsureCE es (NegType t)) => CanNeg (CollectErrors es t) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type NegType (CollectErrors es t) :: Type Source #

not :: CanNeg t => t -> NegType t Source #

A synonym of negate.

type CanNegSameType t = (CanNeg t, NegType t ~ t) Source #

Tests

specCanNegBool :: (Show t, Show (NegType (NegType t)), Serial IO t, CanTestCertainly t, CanTestCertainly (NegType t), CanTestCertainly (NegType (NegType t)), CanNeg t, CanNeg (NegType t)) => T t -> Spec Source #

HSpec properties that each Boolean implementation of CanNeg should satisfy.

And and or

type CanAndOr t1 t2 = (CanAndOrAsymmetric t1 t2, CanAndOrAsymmetric t2 t1, AndOrType t1 t2 ~ AndOrType t2 t1) Source #

class CanAndOrAsymmetric t1 t2 where Source #

Binary logical and and or for generalised Booleans. For example:

 (Just True) && False = Just False
 (Just (Just True)) || False = (Just (Just True))
 

Associated Types

type AndOrType t1 t2 Source #

Methods

and2 :: t1 -> t2 -> AndOrType t1 t2 Source #

or2 :: t1 -> t2 -> AndOrType t1 t2 Source #

Instances
CanAndOrAsymmetric Bool Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType Bool Bool :: Type Source #

(CanAndOrAsymmetric Bool t2, CanTestCertainly t2, CanTestCertainly (AndOrType Bool t2)) => CanAndOrAsymmetric Bool (Maybe t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType Bool (Maybe t2) :: Type Source #

Methods

and2 :: Bool -> Maybe t2 -> AndOrType Bool (Maybe t2) Source #

or2 :: Bool -> Maybe t2 -> AndOrType Bool (Maybe t2) Source #

(CanAndOrAsymmetric Bool t2, SuitableForCE es, CanEnsureCE es t2, CanEnsureCE es (AndOrType Bool t2)) => CanAndOrAsymmetric Bool (CollectErrors es t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType Bool (CollectErrors es t2) :: Type Source #

(CanAndOrAsymmetric t1 Bool, CanTestCertainly t1, CanTestCertainly (AndOrType t1 Bool)) => CanAndOrAsymmetric (Maybe t1) Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType (Maybe t1) Bool :: Type Source #

Methods

and2 :: Maybe t1 -> Bool -> AndOrType (Maybe t1) Bool Source #

or2 :: Maybe t1 -> Bool -> AndOrType (Maybe t1) Bool Source #

(CanAndOrAsymmetric t1 t2, CanTestCertainly t1, CanTestCertainly t2, CanTestCertainly (AndOrType t1 t2)) => CanAndOrAsymmetric (Maybe t1) (Maybe t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType (Maybe t1) (Maybe t2) :: Type Source #

Methods

and2 :: Maybe t1 -> Maybe t2 -> AndOrType (Maybe t1) (Maybe t2) Source #

or2 :: Maybe t1 -> Maybe t2 -> AndOrType (Maybe t1) (Maybe t2) Source #

(CanAndOrAsymmetric t1 Bool, SuitableForCE es, CanEnsureCE es t1, CanEnsureCE es (AndOrType t1 Bool)) => CanAndOrAsymmetric (CollectErrors es t1) Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType (CollectErrors es t1) Bool :: Type Source #

(CanAndOrAsymmetric t1 t2, SuitableForCE es, CanEnsureCE es t1, CanEnsureCE es t2, CanEnsureCE es (AndOrType t1 t2)) => CanAndOrAsymmetric (CollectErrors es t1) (CollectErrors es t2) Source # 
Instance details

Defined in Numeric.MixedTypes.Bool

Associated Types

type AndOrType (CollectErrors es t1) (CollectErrors es t2) :: Type Source #

(&&) :: CanAndOrAsymmetric a b => a -> b -> AndOrType a b infixr 3 Source #

A synonym of and2.

(||) :: CanAndOrAsymmetric a b => a -> b -> AndOrType a b infixr 2 Source #

A synonym of or2.

type CanAndOrWith t1 t2 = (CanAndOr t1 t2, AndOrType t1 t2 ~ t1) Source #

Tests

specCanAndOr :: (Show t1, Show t2, Show t3, Show (AndOrType t1 t1), Show (AndOrType t1 t2), Show (AndOrType t2 t1), Show (AndOrType t1 (AndOrType t2 t3)), Show (AndOrType (AndOrType t1 t2) t3), Show (AndOrType (AndOrType t1 t2) (AndOrType t1 t3)), Show (NegType (AndOrType t1 t2)), Show (AndOrType (NegType t1) (NegType t2)), Serial IO t1, Serial IO t2, Serial IO t3, CanTestCertainly t1, CanTestCertainly (AndOrType t1 t1), CanTestCertainly (AndOrType t1 t2), CanTestCertainly (AndOrType t2 t1), CanTestCertainly (AndOrType t1 (AndOrType t2 t3)), CanTestCertainly (AndOrType (AndOrType t1 t2) t3), CanTestCertainly (AndOrType (AndOrType t1 t2) (AndOrType t1 t3)), CanTestCertainly (NegType (AndOrType t1 t2)), CanTestCertainly (AndOrType (NegType t1) (NegType t2)), CanNeg t1, CanNeg t2, CanNeg (AndOrType t1 t2), CanAndOrAsymmetric t1 t1, CanAndOrAsymmetric t1 t2, CanAndOrAsymmetric t1 t3, CanAndOrAsymmetric t1 (AndOrType t2 t3), CanAndOrAsymmetric t2 t1, CanAndOrAsymmetric t2 t3, CanAndOrAsymmetric (AndOrType t1 t2) t3, CanAndOrAsymmetric (AndOrType t1 t2) (AndOrType t1 t3), CanAndOrAsymmetric (NegType t1) (NegType t2)) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanAndOr should satisfy.

Orphan instances