quickcheck-monoid-subclasses-0.0.0.0: Testing monoid subclass instances with QuickCheck
Copyright© 2022 Jonathan Knowles
LicenseApache-2.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.QuickCheck.Classes.Monoid.GCD

Description

This module provides Laws definitions for classes exported by Data.Monoid.GCD.

Synopsis

Documentation

gcdMonoidLaws :: forall a. (Arbitrary a, Show a, Eq a, GCDMonoid a) => Proxy a -> Laws Source #

Laws for instances of GCDMonoid.

Tests the following laws:

gcd a b == commonPrefix a b
gcd a b == commonSuffix a b
isJust (a </> gcd a b)
isJust (b </> gcd a b)

Note that the following superclass laws are not included:

cancellativeGCDMonoidLaws :: forall a. (Arbitrary a, Show a, Eq a, Cancellative a, GCDMonoid a) => Proxy a -> Laws Source #

Laws for instances of Cancellative and GCDMonoid.

Tests the following laws:

gcd (a <> b) (a <> c) == a <> gcd b c
gcd (a <> c) (b <> c) == gcd a b <> c

Note that the following superclass laws are not included:

leftGCDMonoidLaws :: forall a. (Arbitrary a, Show a, Eq a, LeftGCDMonoid a) => Proxy a -> Laws Source #

Laws for instances of LeftGCDMonoid.

Tests the following laws:

stripCommonPrefix a b & \(p, _, _) -> p == commonPrefix a b
stripCommonPrefix a b & \(p, x, _) -> p <> x == a
stripCommonPrefix a b & \(p, _, x) -> p <> x == b
stripCommonPrefix a b & \(p, x, _) -> Just x == stripPrefix p a
stripCommonPrefix a b & \(p, _, x) -> Just x == stripPrefix p b

Note that the following superclass laws are not included:

rightGCDMonoidLaws :: forall a. (Arbitrary a, Show a, Eq a, RightGCDMonoid a) => Proxy a -> Laws Source #

Laws for instances of RightGCDMonoid.

Tests the following laws:

stripCommonSuffix a b & \(_, _, s) -> s == commonSuffix a b
stripCommonSuffix a b & \(x, _, s) -> x <> s == a
stripCommonSuffix a b & \(_, x, s) -> x <> s == b
stripCommonSuffix a b & \(x, _, s) -> Just x == stripSuffix s a
stripCommonSuffix a b & \(_, x, s) -> Just x == stripSuffix s b

Note that the following superclass laws are not included:

overlappingGCDMonoidLaws :: forall a. (Arbitrary a, Show a, Eq a, OverlappingGCDMonoid a) => Proxy a -> Laws Source #

Laws for instances of OverlappingGCDMonoid.

Tests the following laws:

overlap a b <> stripPrefixOverlap a b == b
stripSuffixOverlap b a <> overlap a b == a
stripOverlap a b & \(_, x, _) -> x == overlap a b
stripOverlap a b & \(_, _, x) -> x == stripPrefixOverlap a b
stripOverlap a b & \(x, _, _) -> x == stripSuffixOverlap b a

Note that the following superclass laws are not included: