{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
module Internal.Semigroup.Tuple
where
import Prelude
import Data.Functor
( (<&>) )
import Data.List.NonEmpty
( NonEmpty (..) )
import GHC.Generics
( Generic )
import Test.QuickCheck
( Arbitrary (..)
, Gen
, applyArbitrary2
, applyArbitrary3
, applyArbitrary4
, choose
, genericShrink
, oneof
, shuffle
, suchThatMap
)
import Text.Show.Pretty
( ppShow )
import qualified Data.Foldable as F
import qualified Data.List.NonEmpty as NE
import qualified Data.Semigroup.Foldable as F1
data Variable = A | B | C | D
deriving (Variable
Variable -> Variable -> Bounded Variable
forall a. a -> a -> Bounded a
$cminBound :: Variable
minBound :: Variable
$cmaxBound :: Variable
maxBound :: Variable
Bounded, Int -> Variable
Variable -> Int
Variable -> [Variable]
Variable -> Variable
Variable -> Variable -> [Variable]
Variable -> Variable -> Variable -> [Variable]
(Variable -> Variable)
-> (Variable -> Variable)
-> (Int -> Variable)
-> (Variable -> Int)
-> (Variable -> [Variable])
-> (Variable -> Variable -> [Variable])
-> (Variable -> Variable -> [Variable])
-> (Variable -> Variable -> Variable -> [Variable])
-> Enum Variable
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Variable -> Variable
succ :: Variable -> Variable
$cpred :: Variable -> Variable
pred :: Variable -> Variable
$ctoEnum :: Int -> Variable
toEnum :: Int -> Variable
$cfromEnum :: Variable -> Int
fromEnum :: Variable -> Int
$cenumFrom :: Variable -> [Variable]
enumFrom :: Variable -> [Variable]
$cenumFromThen :: Variable -> Variable -> [Variable]
enumFromThen :: Variable -> Variable -> [Variable]
$cenumFromTo :: Variable -> Variable -> [Variable]
enumFromTo :: Variable -> Variable -> [Variable]
$cenumFromThenTo :: Variable -> Variable -> Variable -> [Variable]
enumFromThenTo :: Variable -> Variable -> Variable -> [Variable]
Enum, Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, Eq Variable
Eq Variable =>
(Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Variable -> Variable -> Ordering
compare :: Variable -> Variable -> Ordering
$c< :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
>= :: Variable -> Variable -> Bool
$cmax :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
min :: Variable -> Variable -> Variable
Ord, Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variable -> ShowS
showsPrec :: Int -> Variable -> ShowS
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> ShowS
showList :: [Variable] -> ShowS
Show)
bindVariable :: BindingSet s -> Variable -> s
bindVariable :: forall s. BindingSet s -> Variable -> s
bindVariable BindingSet {s
bindingForA :: s
bindingForA :: forall s. BindingSet s -> s
bindingForA} Variable
A = s
bindingForA
bindVariable BindingSet {s
bindingForB :: s
bindingForB :: forall s. BindingSet s -> s
bindingForB} Variable
B = s
bindingForB
bindVariable BindingSet {s
bindingForC :: s
bindingForC :: forall s. BindingSet s -> s
bindingForC} Variable
C = s
bindingForC
bindVariable BindingSet {s
bindingForD :: s
bindingForD :: forall s. BindingSet s -> s
bindingForD} Variable
D = s
bindingForD
newtype VariableSum = VariableSum (NonEmpty Variable)
deriving (VariableSum -> VariableSum -> Bool
(VariableSum -> VariableSum -> Bool)
-> (VariableSum -> VariableSum -> Bool) -> Eq VariableSum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariableSum -> VariableSum -> Bool
== :: VariableSum -> VariableSum -> Bool
$c/= :: VariableSum -> VariableSum -> Bool
/= :: VariableSum -> VariableSum -> Bool
Eq, Eq VariableSum
Eq VariableSum =>
(VariableSum -> VariableSum -> Ordering)
-> (VariableSum -> VariableSum -> Bool)
-> (VariableSum -> VariableSum -> Bool)
-> (VariableSum -> VariableSum -> Bool)
-> (VariableSum -> VariableSum -> Bool)
-> (VariableSum -> VariableSum -> VariableSum)
-> (VariableSum -> VariableSum -> VariableSum)
-> Ord VariableSum
VariableSum -> VariableSum -> Bool
VariableSum -> VariableSum -> Ordering
VariableSum -> VariableSum -> VariableSum
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VariableSum -> VariableSum -> Ordering
compare :: VariableSum -> VariableSum -> Ordering
$c< :: VariableSum -> VariableSum -> Bool
< :: VariableSum -> VariableSum -> Bool
$c<= :: VariableSum -> VariableSum -> Bool
<= :: VariableSum -> VariableSum -> Bool
$c> :: VariableSum -> VariableSum -> Bool
> :: VariableSum -> VariableSum -> Bool
$c>= :: VariableSum -> VariableSum -> Bool
>= :: VariableSum -> VariableSum -> Bool
$cmax :: VariableSum -> VariableSum -> VariableSum
max :: VariableSum -> VariableSum -> VariableSum
$cmin :: VariableSum -> VariableSum -> VariableSum
min :: VariableSum -> VariableSum -> VariableSum
Ord, NonEmpty VariableSum -> VariableSum
VariableSum -> VariableSum -> VariableSum
(VariableSum -> VariableSum -> VariableSum)
-> (NonEmpty VariableSum -> VariableSum)
-> (forall b. Integral b => b -> VariableSum -> VariableSum)
-> Semigroup VariableSum
forall b. Integral b => b -> VariableSum -> VariableSum
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: VariableSum -> VariableSum -> VariableSum
<> :: VariableSum -> VariableSum -> VariableSum
$csconcat :: NonEmpty VariableSum -> VariableSum
sconcat :: NonEmpty VariableSum -> VariableSum
$cstimes :: forall b. Integral b => b -> VariableSum -> VariableSum
stimes :: forall b. Integral b => b -> VariableSum -> VariableSum
Semigroup)
instance Arbitrary VariableSum where
arbitrary :: Gen VariableSum
arbitrary = Gen VariableSum
genVariableSum
instance Show VariableSum where
show :: VariableSum -> String
show (VariableSum NonEmpty Variable
vs) = String -> NonEmpty String -> String
forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => m -> t m -> m
F1.intercalate1 String
" <> " (NonEmpty String -> String) -> NonEmpty String -> String
forall a b. (a -> b) -> a -> b
$ Variable -> String
forall a. Show a => a -> String
show (Variable -> String) -> NonEmpty Variable -> NonEmpty String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty Variable
vs
a, b, c, d :: VariableSum
a :: VariableSum
a = NonEmpty Variable -> VariableSum
VariableSum (Variable
A Variable -> [Variable] -> NonEmpty Variable
forall a. a -> [a] -> NonEmpty a
:| [])
b :: VariableSum
b = NonEmpty Variable -> VariableSum
VariableSum (Variable
B Variable -> [Variable] -> NonEmpty Variable
forall a. a -> [a] -> NonEmpty a
:| [])
c :: VariableSum
c = NonEmpty Variable -> VariableSum
VariableSum (Variable
C Variable -> [Variable] -> NonEmpty Variable
forall a. a -> [a] -> NonEmpty a
:| [])
d :: VariableSum
d = NonEmpty Variable -> VariableSum
VariableSum (Variable
D Variable -> [Variable] -> NonEmpty Variable
forall a. a -> [a] -> NonEmpty a
:| [])
genVariableSum :: Gen VariableSum
genVariableSum :: Gen VariableSum
genVariableSum =
NonEmpty Variable -> VariableSum
VariableSum (NonEmpty Variable -> VariableSum)
-> Gen (NonEmpty Variable) -> Gen VariableSum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [Variable]
genVariableList Gen [Variable]
-> ([Variable] -> Maybe (NonEmpty Variable))
-> Gen (NonEmpty Variable)
forall a b. Gen a -> (a -> Maybe b) -> Gen b
`suchThatMap` [Variable] -> Maybe (NonEmpty Variable)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty
where
genVariableList :: Gen [Variable]
genVariableList :: Gen [Variable]
genVariableList = do
Int
itemCount <- (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
choose (Int
1, Int
4)
Int -> [Variable] -> [Variable]
forall a. Int -> [a] -> [a]
take Int
itemCount ([Variable] -> [Variable]) -> Gen [Variable] -> Gen [Variable]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Variable] -> Gen [Variable]
forall a. [a] -> Gen [a]
shuffle [Variable]
forall a. (Bounded a, Enum a) => [a]
universe
bindVariableSum :: BindingSet s -> VariableSum -> NonEmpty s
bindVariableSum :: forall s. BindingSet s -> VariableSum -> NonEmpty s
bindVariableSum BindingSet s
tuple (VariableSum NonEmpty Variable
selectors) =
BindingSet s -> Variable -> s
forall s. BindingSet s -> Variable -> s
bindVariable BindingSet s
tuple (Variable -> s) -> NonEmpty Variable -> NonEmpty s
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty Variable
selectors
evalVariableSum :: Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum :: forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum = (NonEmpty s -> s
forall m. Semigroup m => NonEmpty m -> m
forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 (NonEmpty s -> s)
-> (VariableSum -> NonEmpty s) -> VariableSum -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((VariableSum -> NonEmpty s) -> VariableSum -> s)
-> (BindingSet s -> VariableSum -> NonEmpty s)
-> BindingSet s
-> VariableSum
-> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BindingSet s -> VariableSum -> NonEmpty s
forall s. BindingSet s -> VariableSum -> NonEmpty s
bindVariableSum
showVariableSum :: Show s => (BindingSet s) -> VariableSum -> String
showVariableSum :: forall s. Show s => BindingSet s -> VariableSum -> String
showVariableSum BindingSet s
tuple =
String -> (s -> String) -> NonEmpty s -> String
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
m -> (a -> m) -> t a -> m
F1.intercalateMap1 String
" <> " s -> String
forall a. Show a => a -> String
show (NonEmpty s -> String)
-> (VariableSum -> NonEmpty s) -> VariableSum -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BindingSet s -> VariableSum -> NonEmpty s
forall s. BindingSet s -> VariableSum -> NonEmpty s
bindVariableSum BindingSet s
tuple
data BindingSet s = BindingSet
{ forall s. BindingSet s -> s
bindingForA :: s
, forall s. BindingSet s -> s
bindingForB :: s
, forall s. BindingSet s -> s
bindingForC :: s
, forall s. BindingSet s -> s
bindingForD :: s
}
deriving (BindingSet s -> BindingSet s -> Bool
(BindingSet s -> BindingSet s -> Bool)
-> (BindingSet s -> BindingSet s -> Bool) -> Eq (BindingSet s)
forall s. Eq s => BindingSet s -> BindingSet s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => BindingSet s -> BindingSet s -> Bool
== :: BindingSet s -> BindingSet s -> Bool
$c/= :: forall s. Eq s => BindingSet s -> BindingSet s -> Bool
/= :: BindingSet s -> BindingSet s -> Bool
Eq, (forall x. BindingSet s -> Rep (BindingSet s) x)
-> (forall x. Rep (BindingSet s) x -> BindingSet s)
-> Generic (BindingSet s)
forall x. Rep (BindingSet s) x -> BindingSet s
forall x. BindingSet s -> Rep (BindingSet s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s x. Rep (BindingSet s) x -> BindingSet s
forall s x. BindingSet s -> Rep (BindingSet s) x
$cfrom :: forall s x. BindingSet s -> Rep (BindingSet s) x
from :: forall x. BindingSet s -> Rep (BindingSet s) x
$cto :: forall s x. Rep (BindingSet s) x -> BindingSet s
to :: forall x. Rep (BindingSet s) x -> BindingSet s
Generic, Eq (BindingSet s)
Eq (BindingSet s) =>
(BindingSet s -> BindingSet s -> Ordering)
-> (BindingSet s -> BindingSet s -> Bool)
-> (BindingSet s -> BindingSet s -> Bool)
-> (BindingSet s -> BindingSet s -> Bool)
-> (BindingSet s -> BindingSet s -> Bool)
-> (BindingSet s -> BindingSet s -> BindingSet s)
-> (BindingSet s -> BindingSet s -> BindingSet s)
-> Ord (BindingSet s)
BindingSet s -> BindingSet s -> Bool
BindingSet s -> BindingSet s -> Ordering
BindingSet s -> BindingSet s -> BindingSet s
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s. Ord s => Eq (BindingSet s)
forall s. Ord s => BindingSet s -> BindingSet s -> Bool
forall s. Ord s => BindingSet s -> BindingSet s -> Ordering
forall s. Ord s => BindingSet s -> BindingSet s -> BindingSet s
$ccompare :: forall s. Ord s => BindingSet s -> BindingSet s -> Ordering
compare :: BindingSet s -> BindingSet s -> Ordering
$c< :: forall s. Ord s => BindingSet s -> BindingSet s -> Bool
< :: BindingSet s -> BindingSet s -> Bool
$c<= :: forall s. Ord s => BindingSet s -> BindingSet s -> Bool
<= :: BindingSet s -> BindingSet s -> Bool
$c> :: forall s. Ord s => BindingSet s -> BindingSet s -> Bool
> :: BindingSet s -> BindingSet s -> Bool
$c>= :: forall s. Ord s => BindingSet s -> BindingSet s -> Bool
>= :: BindingSet s -> BindingSet s -> Bool
$cmax :: forall s. Ord s => BindingSet s -> BindingSet s -> BindingSet s
max :: BindingSet s -> BindingSet s -> BindingSet s
$cmin :: forall s. Ord s => BindingSet s -> BindingSet s -> BindingSet s
min :: BindingSet s -> BindingSet s -> BindingSet s
Ord)
instance Show s => Show (BindingSet s) where
show :: BindingSet s -> String
show (BindingSet s
va s
vb s
vc s
vd) = [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"BindingSet {"
, String
"a = " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> s -> String
forall a. Show a => a -> String
show s
va String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", "
, String
"b = " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> s -> String
forall a. Show a => a -> String
show s
vb String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", "
, String
"c = " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> s -> String
forall a. Show a => a -> String
show s
vc String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", "
, String
"d = " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> s -> String
forall a. Show a => a -> String
show s
vd
, String
"}"
]
instance Arbitrary s => Arbitrary (BindingSet s) where
arbitrary :: Gen (BindingSet s)
arbitrary = Gen (BindingSet s)
forall s. Arbitrary s => Gen (BindingSet s)
genBindingSet
shrink :: BindingSet s -> [BindingSet s]
shrink = BindingSet s -> [BindingSet s]
forall s. Arbitrary s => BindingSet s -> [BindingSet s]
shrinkBindingSet
genBindingSet :: Arbitrary s => Gen (BindingSet s)
genBindingSet :: forall s. Arbitrary s => Gen (BindingSet s)
genBindingSet = (s -> s -> s -> s -> BindingSet s) -> Gen (BindingSet s)
forall a b c d r.
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) =>
(a -> b -> c -> d -> r) -> Gen r
applyArbitrary4 s -> s -> s -> s -> BindingSet s
forall s. s -> s -> s -> s -> BindingSet s
BindingSet
shrinkBindingSet :: Arbitrary s => BindingSet s -> [BindingSet s]
shrinkBindingSet :: forall s. Arbitrary s => BindingSet s -> [BindingSet s]
shrinkBindingSet = BindingSet s -> [BindingSet s]
forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
data Tuple1 s = Tuple1 VariableSum (BindingSet s)
deriving (Tuple1 s -> Tuple1 s -> Bool
(Tuple1 s -> Tuple1 s -> Bool)
-> (Tuple1 s -> Tuple1 s -> Bool) -> Eq (Tuple1 s)
forall s. Eq s => Tuple1 s -> Tuple1 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => Tuple1 s -> Tuple1 s -> Bool
== :: Tuple1 s -> Tuple1 s -> Bool
$c/= :: forall s. Eq s => Tuple1 s -> Tuple1 s -> Bool
/= :: Tuple1 s -> Tuple1 s -> Bool
Eq, Eq (Tuple1 s)
Eq (Tuple1 s) =>
(Tuple1 s -> Tuple1 s -> Ordering)
-> (Tuple1 s -> Tuple1 s -> Bool)
-> (Tuple1 s -> Tuple1 s -> Bool)
-> (Tuple1 s -> Tuple1 s -> Bool)
-> (Tuple1 s -> Tuple1 s -> Bool)
-> (Tuple1 s -> Tuple1 s -> Tuple1 s)
-> (Tuple1 s -> Tuple1 s -> Tuple1 s)
-> Ord (Tuple1 s)
Tuple1 s -> Tuple1 s -> Bool
Tuple1 s -> Tuple1 s -> Ordering
Tuple1 s -> Tuple1 s -> Tuple1 s
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s. Ord s => Eq (Tuple1 s)
forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
forall s. Ord s => Tuple1 s -> Tuple1 s -> Ordering
forall s. Ord s => Tuple1 s -> Tuple1 s -> Tuple1 s
$ccompare :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Ordering
compare :: Tuple1 s -> Tuple1 s -> Ordering
$c< :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
< :: Tuple1 s -> Tuple1 s -> Bool
$c<= :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
<= :: Tuple1 s -> Tuple1 s -> Bool
$c> :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
> :: Tuple1 s -> Tuple1 s -> Bool
$c>= :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
>= :: Tuple1 s -> Tuple1 s -> Bool
$cmax :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Tuple1 s
max :: Tuple1 s -> Tuple1 s -> Tuple1 s
$cmin :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Tuple1 s
min :: Tuple1 s -> Tuple1 s -> Tuple1 s
Ord)
data Tuple2 s = Tuple2 VariableSum VariableSum (BindingSet s)
deriving (Tuple2 s -> Tuple2 s -> Bool
(Tuple2 s -> Tuple2 s -> Bool)
-> (Tuple2 s -> Tuple2 s -> Bool) -> Eq (Tuple2 s)
forall s. Eq s => Tuple2 s -> Tuple2 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => Tuple2 s -> Tuple2 s -> Bool
== :: Tuple2 s -> Tuple2 s -> Bool
$c/= :: forall s. Eq s => Tuple2 s -> Tuple2 s -> Bool
/= :: Tuple2 s -> Tuple2 s -> Bool
Eq, Eq (Tuple2 s)
Eq (Tuple2 s) =>
(Tuple2 s -> Tuple2 s -> Ordering)
-> (Tuple2 s -> Tuple2 s -> Bool)
-> (Tuple2 s -> Tuple2 s -> Bool)
-> (Tuple2 s -> Tuple2 s -> Bool)
-> (Tuple2 s -> Tuple2 s -> Bool)
-> (Tuple2 s -> Tuple2 s -> Tuple2 s)
-> (Tuple2 s -> Tuple2 s -> Tuple2 s)
-> Ord (Tuple2 s)
Tuple2 s -> Tuple2 s -> Bool
Tuple2 s -> Tuple2 s -> Ordering
Tuple2 s -> Tuple2 s -> Tuple2 s
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s. Ord s => Eq (Tuple2 s)
forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
forall s. Ord s => Tuple2 s -> Tuple2 s -> Ordering
forall s. Ord s => Tuple2 s -> Tuple2 s -> Tuple2 s
$ccompare :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Ordering
compare :: Tuple2 s -> Tuple2 s -> Ordering
$c< :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
< :: Tuple2 s -> Tuple2 s -> Bool
$c<= :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
<= :: Tuple2 s -> Tuple2 s -> Bool
$c> :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
> :: Tuple2 s -> Tuple2 s -> Bool
$c>= :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
>= :: Tuple2 s -> Tuple2 s -> Bool
$cmax :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Tuple2 s
max :: Tuple2 s -> Tuple2 s -> Tuple2 s
$cmin :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Tuple2 s
min :: Tuple2 s -> Tuple2 s -> Tuple2 s
Ord)
data Tuple3 s = Tuple3 VariableSum VariableSum VariableSum (BindingSet s)
deriving (Tuple3 s -> Tuple3 s -> Bool
(Tuple3 s -> Tuple3 s -> Bool)
-> (Tuple3 s -> Tuple3 s -> Bool) -> Eq (Tuple3 s)
forall s. Eq s => Tuple3 s -> Tuple3 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => Tuple3 s -> Tuple3 s -> Bool
== :: Tuple3 s -> Tuple3 s -> Bool
$c/= :: forall s. Eq s => Tuple3 s -> Tuple3 s -> Bool
/= :: Tuple3 s -> Tuple3 s -> Bool
Eq, Eq (Tuple3 s)
Eq (Tuple3 s) =>
(Tuple3 s -> Tuple3 s -> Ordering)
-> (Tuple3 s -> Tuple3 s -> Bool)
-> (Tuple3 s -> Tuple3 s -> Bool)
-> (Tuple3 s -> Tuple3 s -> Bool)
-> (Tuple3 s -> Tuple3 s -> Bool)
-> (Tuple3 s -> Tuple3 s -> Tuple3 s)
-> (Tuple3 s -> Tuple3 s -> Tuple3 s)
-> Ord (Tuple3 s)
Tuple3 s -> Tuple3 s -> Bool
Tuple3 s -> Tuple3 s -> Ordering
Tuple3 s -> Tuple3 s -> Tuple3 s
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s. Ord s => Eq (Tuple3 s)
forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
forall s. Ord s => Tuple3 s -> Tuple3 s -> Ordering
forall s. Ord s => Tuple3 s -> Tuple3 s -> Tuple3 s
$ccompare :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Ordering
compare :: Tuple3 s -> Tuple3 s -> Ordering
$c< :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
< :: Tuple3 s -> Tuple3 s -> Bool
$c<= :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
<= :: Tuple3 s -> Tuple3 s -> Bool
$c> :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
> :: Tuple3 s -> Tuple3 s -> Bool
$c>= :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
>= :: Tuple3 s -> Tuple3 s -> Bool
$cmax :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Tuple3 s
max :: Tuple3 s -> Tuple3 s -> Tuple3 s
$cmin :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Tuple3 s
min :: Tuple3 s -> Tuple3 s -> Tuple3 s
Ord)
instance Arbitrary a => Arbitrary (Tuple1 a) where
arbitrary :: Gen (Tuple1 a)
arbitrary = Gen (Tuple1 a)
forall a. Arbitrary a => Gen (Tuple1 a)
genTuple1
shrink :: Tuple1 a -> [Tuple1 a]
shrink = Tuple1 a -> [Tuple1 a]
forall a. Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1
instance Arbitrary a => Arbitrary (Tuple2 a) where
arbitrary :: Gen (Tuple2 a)
arbitrary = Gen (Tuple2 a)
forall a. Arbitrary a => Gen (Tuple2 a)
genTuple2
shrink :: Tuple2 a -> [Tuple2 a]
shrink = Tuple2 a -> [Tuple2 a]
forall a. Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2
instance Arbitrary a => Arbitrary (Tuple3 a) where
arbitrary :: Gen (Tuple3 a)
arbitrary = Gen (Tuple3 a)
forall a. Arbitrary a => Gen (Tuple3 a)
genTuple3
shrink :: Tuple3 a -> [Tuple3 a]
shrink = Tuple3 a -> [Tuple3 a]
forall a. Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3
instance (Show s, Semigroup s) => Show (Tuple1 s) where
show :: Tuple1 s -> String
show = Tuple1 s -> String
forall a. (Semigroup a, Show a) => Tuple1 a -> String
showTuple1
instance (Show s, Semigroup s) => Show (Tuple2 s) where
show :: Tuple2 s -> String
show = Tuple2 s -> String
forall a. (Semigroup a, Show a) => Tuple2 a -> String
showTuple2
instance (Show s, Semigroup s) => Show (Tuple3 s) where
show :: Tuple3 s -> String
show = Tuple3 s -> String
forall a. (Semigroup a, Show a) => Tuple3 a -> String
showTuple3
genTuple1 :: Arbitrary a => Gen (Tuple1 a)
genTuple1 :: forall a. Arbitrary a => Gen (Tuple1 a)
genTuple1 = (VariableSum -> BindingSet a -> Tuple1 a) -> Gen (Tuple1 a)
forall a b r. (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r
applyArbitrary2 VariableSum -> BindingSet a -> Tuple1 a
forall s. VariableSum -> BindingSet s -> Tuple1 s
Tuple1
genTuple2 :: forall a. Arbitrary a => Gen (Tuple2 a)
genTuple2 :: forall a. Arbitrary a => Gen (Tuple2 a)
genTuple2 = [Gen (Tuple2 a)] -> Gen (Tuple2 a)
forall a. HasCallStack => [Gen a] -> Gen a
oneof [Gen (Tuple2 a)
genRandom, Gen (Tuple2 a)
genHandChosen]
where
genRandom :: Gen (Tuple2 a)
genRandom :: Gen (Tuple2 a)
genRandom = (VariableSum -> VariableSum -> BindingSet a -> Tuple2 a)
-> Gen (Tuple2 a)
forall a b c r.
(Arbitrary a, Arbitrary b, Arbitrary c) =>
(a -> b -> c -> r) -> Gen r
applyArbitrary3 VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2
genHandChosen :: Gen (Tuple2 a)
genHandChosen :: Gen (Tuple2 a)
genHandChosen = [Gen (Tuple2 a)] -> Gen (Tuple2 a)
forall a. HasCallStack => [Gen a] -> Gen a
oneof ([Gen (Tuple2 a)] -> Gen (Tuple2 a))
-> [Gen (Tuple2 a)] -> Gen (Tuple2 a)
forall a b. (a -> b) -> a -> b
$ ((BindingSet a -> Tuple2 a) -> Gen (Tuple2 a))
-> [BindingSet a -> Tuple2 a] -> [Gen (Tuple2 a)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Gen (BindingSet a)
forall a. Arbitrary a => Gen a
arbitrary Gen (BindingSet a) -> (BindingSet a -> Tuple2 a) -> Gen (Tuple2 a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>)
[
VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 VariableSum
a VariableSum
a
,
VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 VariableSum
a VariableSum
b
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
c VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
a)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
a)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
b) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b)
, VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
b)
]
genTuple3 :: forall a. Arbitrary a => Gen (Tuple3 a)
genTuple3 :: forall a. Arbitrary a => Gen (Tuple3 a)
genTuple3 = [Gen (Tuple3 a)] -> Gen (Tuple3 a)
forall a. HasCallStack => [Gen a] -> Gen a
oneof [Gen (Tuple3 a)
genRandom, Gen (Tuple3 a)
genHandChosen]
where
genRandom :: Gen (Tuple3 a)
genRandom :: Gen (Tuple3 a)
genRandom = (VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a)
-> Gen (Tuple3 a)
forall a b c d r.
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) =>
(a -> b -> c -> d -> r) -> Gen r
applyArbitrary4 VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3
genHandChosen :: Gen (Tuple3 a)
genHandChosen :: Gen (Tuple3 a)
genHandChosen = [Gen (Tuple3 a)] -> Gen (Tuple3 a)
forall a. HasCallStack => [Gen a] -> Gen a
oneof ([Gen (Tuple3 a)] -> Gen (Tuple3 a))
-> [Gen (Tuple3 a)] -> Gen (Tuple3 a)
forall a b. (a -> b) -> a -> b
$ ((BindingSet a -> Tuple3 a) -> Gen (Tuple3 a))
-> [BindingSet a -> Tuple3 a] -> [Gen (Tuple3 a)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Gen (BindingSet a)
forall a. Arbitrary a => Gen a
arbitrary Gen (BindingSet a) -> (BindingSet a -> Tuple3 a) -> Gen (Tuple3 a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>)
[
VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 VariableSum
a VariableSum
a VariableSum
a
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 VariableSum
a VariableSum
b VariableSum
c
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
d)
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
d) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
d) (VariableSum
c VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
d)
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
a) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c)
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b) (VariableSum
a)
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
c) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c)
, VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 (VariableSum
a VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
b VariableSum -> VariableSum -> VariableSum
forall a. Semigroup a => a -> a -> a
<> VariableSum
c) (VariableSum
c)
]
evalTuple1 :: Semigroup s => Tuple1 s -> s
evalTuple1 :: forall s. Semigroup s => Tuple1 s -> s
evalTuple1 (Tuple1 VariableSum
c1 BindingSet s
t) =
( BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c1
)
evalTuple2 :: Semigroup s => Tuple2 s -> (s, s)
evalTuple2 :: forall s. Semigroup s => Tuple2 s -> (s, s)
evalTuple2 (Tuple2 VariableSum
c1 VariableSum
c2 BindingSet s
t) =
( BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c1
, BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c2
)
evalTuple3 :: Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 :: forall s. Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 (Tuple3 VariableSum
c1 VariableSum
c2 VariableSum
c3 BindingSet s
t) =
( BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c1
, BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c2
, BindingSet s -> VariableSum -> s
forall s. Semigroup s => BindingSet s -> VariableSum -> s
evalVariableSum BindingSet s
t VariableSum
c3
)
showTuple1 :: (Semigroup a, Show a) => Tuple1 a -> String
showTuple1 :: forall a. (Semigroup a, Show a) => Tuple1 a -> String
showTuple1 (Tuple1 a -> a
forall s. Semigroup s => Tuple1 s -> s
evalTuple1 -> a
va) = [String] -> String
unlines
[ String
forall a. Monoid a => a
mempty, String
"a:", a -> String
forall a. Show a => a -> String
showWrap a
va
]
showTuple2 :: (Semigroup a, Show a) => Tuple2 a -> String
showTuple2 :: forall a. (Semigroup a, Show a) => Tuple2 a -> String
showTuple2 (Tuple2 a -> (a, a)
forall s. Semigroup s => Tuple2 s -> (s, s)
evalTuple2 -> (a
va, a
vb)) = [String] -> String
unlines
[ String
forall a. Monoid a => a
mempty, String
"a:", a -> String
forall a. Show a => a -> String
showWrap a
va
, String
forall a. Monoid a => a
mempty, String
"b:", a -> String
forall a. Show a => a -> String
showWrap a
vb
]
showTuple3 :: (Semigroup a, Show a) => Tuple3 a -> String
showTuple3 :: forall a. (Semigroup a, Show a) => Tuple3 a -> String
showTuple3 (Tuple3 a -> (a, a, a)
forall s. Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 -> (a
va, a
vb, a
vc)) = [String] -> String
unlines
[ String
forall a. Monoid a => a
mempty, String
"a:", a -> String
forall a. Show a => a -> String
showWrap a
va
, String
forall a. Monoid a => a
mempty, String
"b:", a -> String
forall a. Show a => a -> String
showWrap a
vb
, String
forall a. Monoid a => a
mempty, String
"c:", a -> String
forall a. Show a => a -> String
showWrap a
vc
]
shrinkTuple1 :: Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1 :: forall a. Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1 (Tuple1 VariableSum
c1 BindingSet a
t) = VariableSum -> BindingSet a -> Tuple1 a
forall s. VariableSum -> BindingSet s -> Tuple1 s
Tuple1 VariableSum
c1 (BindingSet a -> Tuple1 a) -> [BindingSet a] -> [Tuple1 a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BindingSet a -> [BindingSet a]
forall a. Arbitrary a => a -> [a]
shrink BindingSet a
t
shrinkTuple2 :: Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2 :: forall a. Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2 (Tuple2 VariableSum
c1 VariableSum
c2 BindingSet a
t) = VariableSum -> VariableSum -> BindingSet a -> Tuple2 a
forall s. VariableSum -> VariableSum -> BindingSet s -> Tuple2 s
Tuple2 VariableSum
c1 VariableSum
c2 (BindingSet a -> Tuple2 a) -> [BindingSet a] -> [Tuple2 a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BindingSet a -> [BindingSet a]
forall a. Arbitrary a => a -> [a]
shrink BindingSet a
t
shrinkTuple3 :: Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3 :: forall a. Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3 (Tuple3 VariableSum
c1 VariableSum
c2 VariableSum
c3 BindingSet a
t) = VariableSum
-> VariableSum -> VariableSum -> BindingSet a -> Tuple3 a
forall s.
VariableSum
-> VariableSum -> VariableSum -> BindingSet s -> Tuple3 s
Tuple3 VariableSum
c1 VariableSum
c2 VariableSum
c3 (BindingSet a -> Tuple3 a) -> [BindingSet a] -> [Tuple3 a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BindingSet a -> [BindingSet a]
forall a. Arbitrary a => a -> [a]
shrink BindingSet a
t
showWrap :: Show a => a -> String
showWrap :: forall a. Show a => a -> String
showWrap a
x
| Bool
singleLineMaxLengthExceeded =
String
multiLine
| Bool
otherwise =
String
singleLine
where
multiLine :: String
multiLine = a -> String
forall a. Show a => a -> String
ppShow a
x
singleLine :: String
singleLine = a -> String
forall a. Show a => a -> String
show a
x
singleLineMaxLength :: Int
singleLineMaxLength = Int
80
singleLineMaxLengthExceeded :: Bool
singleLineMaxLengthExceeded = String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
F.length String
singleLine Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
singleLineMaxLength
universe :: (Bounded a, Enum a) => [a]
universe :: forall a. (Bounded a, Enum a) => [a]
universe = [a
forall a. Bounded a => a
minBound .. a
forall a. Bounded a => a
maxBound]