semiring-num-1.0.0.0: Basic semiring class and instances

LicenseMIT
Maintainermail@doisinkidney.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Test.Semiring

Contents

Description

This module provides functions which can be quickly converted into smallcheck or QuickCheck-like properties. The functions are of the form:

a -> Either String String

where the left case is failure of the test, and the right case is success.

For smallcheck, this function can be used directly as a property:

smallCheck 10 (plusId :: UnaryLaws Integer)

(the typealias is provided as well)

For QuickCheck, you might want to provide an instance like this:

instance Testable (Either String String) where
  property = either (`counterexample` False) (const (property True))

And then testing is as simple as:

quickCheck (plusAssoc :: TernaryLaws Integer)

There are also functions provided to test multiple laws at once. Putting all of this together, writing a test for all the semiring laws for, say, Integer looks like this:

quickCheck (unaryLaws   :: UnaryLaws   Integer)
quickCheck (binaryLaws  :: BinaryLaws  Integer)
quickCheck (ternaryLaws :: TernaryLaws Integer)

Synopsis

Type Aliases

type UnaryLaws a = a -> Either String String Source #

Typealias for unary laws. Can be used like so:

smallCheck 10 (unaryLaws :: UnaryLaws Int)

type BinaryLaws a = a -> a -> Either String String Source #

Typealias for binary laws. Can be used like so:

smallCheck 8 (binaryLaws :: BinaryLaws Int)

type TernaryLaws a = a -> a -> a -> Either String String Source #

Typealias for ternary laws. Can be used like so:

smallCheck 6 (ternaryLaws :: TernaryLaws Int)

Semiring Laws

Unary

plusId :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

Additive identity.

x <+> zero = zero <+> x = x

mulId :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

Multiplicative identity.

x <.> one = one <.> x = x

annihilateL :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

Left annihilation of <.> by zero.

x <.> zero = zero

annihilateR :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

Right annihilation of <.> by zero.

zero <.> x = zero

unaryLaws :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

A test for all three unary laws for Semirings (plusId, mulId, annihilateL, and annihilateR).

Binary

plusComm :: (Eq a, Semiring a, Show a) => a -> a -> Either String String Source #

Plus is commutative.

x <+> y = y <+> x

binaryLaws :: (Eq a, Semiring a, Show a) => a -> a -> Either String String Source #

A test for all of the binary laws for Semirings (just plusComm).

Ternary

plusAssoc :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Plus is associative.

(x <+> y) <+> z = x <+> (y <+> z)

mulAssoc :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Multiplication is associative.

(x <.> y) <.> z = x <.> (y <.> z)

mulDistribL :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Multiplication distributes left.

x <.> (y <+> z) = x <.> y <+> x <.> z

mulDistribR :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Multiplication distributes right.

(x <+> y) <.> z = x <.> z <+> y <.> z

ternaryLaws :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

A test for all of the ternary laws for Semirings (plusAssoc, mulAssoc, mulDistribL, mulDistribR).

Near-semiring laws

Unary

nearUnaryLaws :: (Eq a, Semiring a, Show a) => a -> Either String String Source #

A test for the unary laws for near-Semirings (plusId, mulId, and annihilateR).

Ternary

nearTernaryLaws :: (Eq a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

A test for all of the ternary laws for near-Semirings (plusAssoc, mulAssoc, mulDistribR).

StarSemiring Laws

Unary

starLaw :: (Eq a, StarSemiring a, Show a) => a -> Either String String Source #

The star law for StarSemirings.

star x = one <+> x <.> star x = one <+> star x <.> x

plusLaw :: (Eq a, StarSemiring a, Show a) => a -> Either String String Source #

The plus law for StarSemirings.

plus x = x <.> star x

DetectableZero Laws

Unary

zeroLaw :: (Eq a, DetectableZero a, Show a) => a -> Either String String Source #

Law for result of isZero operation.

x == zero = zero == x = isZero x

zeroIsZero :: (DetectableZero a, Show a) => f a -> Either String String Source #

Zero is zero law.

isZero zero = True

Ordering Laws

Ternary

ordMulLaw :: (Ord a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Multiplication law for ordered Semirings.

x <= y => x <.> z <= y <.> z && z <.> x <= z <.> y

ordAddLaw :: (Ord a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Addition law for ordered Semirings.

x <= y => x <+> z <= y <+> z && z <+> x <= z <+> y

ordLaws :: (Ord a, Semiring a, Show a) => a -> a -> a -> Either String String Source #

Laws for ordered Semirings (ordMulLaw, ordAddLaw).