mixed-types-num-0.1.0.0: 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)

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.

Minimal complete definition

isCertainlyTrue, isCertainlyFalse

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
 

Minimal complete definition

negate

Associated Types

type NegType t Source #

Methods

negate :: t -> NegType t Source #

Instances

CanNeg Bool Source # 

Associated Types

type NegType Bool :: * Source #

CanNeg t => CanNeg (Maybe t) Source # 

Associated Types

type NegType (Maybe t) :: * Source #

Methods

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

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

A synonym of negate.

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

Tests

specCanNegBool :: (CanNegBoolX t, CanNegBoolX (NegType t)) => T t -> Spec Source #

HSpec properties that each Boolean implementation of CanNeg should satisfy.

type CanNegBoolX t = (CanNeg t, CanTestCertainlyX t, CanTestCertainlyX (NegType t)) Source #

Compound type constraint useful for test definition.

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))
 

Minimal complete definition

and2, or2

Associated Types

type AndOrType t1 t2 Source #

Methods

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

or2 :: t1 -> t2 -> AndOrType t1 t2 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 :: (CanAndOrX t1 t1, CanAndOrX t1 t2, CanAndOrX t2 t1, CanAndOrX t1 t3, CanAndOrX t2 t3, CanAndOrX (AndOrType t1 t2) t3, CanAndOrX t1 (AndOrType t2 t3), CanAndOrX (AndOrType t1 t2) (AndOrType t1 t3)) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanAndOr should satisfy.

specCanAndOrNotMixed :: (CanAndOrX t t, CanAndOrX (AndOrType t t) t, CanAndOrX t (AndOrType t t), CanAndOrX (AndOrType t t) (AndOrType t t)) => T t -> Spec Source #

HSpec properties that each implementation of CanAndOr should satisfy.

type CanAndOrX t1 t2 = (CanAndOr t1 t2, CanNeg t1, CanNeg t2, CanAndOr (NegType t1) t2, CanAndOr t1 (NegType t2), CanAndOr (NegType t1) (NegType t2), CanTestCertainlyX t1, CanTestCertainlyX t2, CanTestCertainlyX (AndOrType t1 t2), CanTestCertainlyX (NegType (AndOrType t1 t2)), CanTestCertainlyX (AndOrType (NegType t1) t2), CanTestCertainlyX (AndOrType t1 (NegType t2)), CanTestCertainlyX (AndOrType (NegType t1) (NegType t2))) Source #

Compound type constraint useful for test definition.

Orphan instances