module Internal.Semigroup.Tuple
where
import Data.List.NonEmpty
( NonEmpty (..) )
import Test.QuickCheck
( Arbitrary (..), Gen, choose, 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 TupleLens3
= TupleLens3A
| TupleLens3B
| TupleLens3C
deriving (TupleLens3
forall a. a -> a -> Bounded a
maxBound :: TupleLens3
$cmaxBound :: TupleLens3
minBound :: TupleLens3
$cminBound :: TupleLens3
Bounded, Int -> TupleLens3
TupleLens3 -> Int
TupleLens3 -> [TupleLens3]
TupleLens3 -> TupleLens3
TupleLens3 -> TupleLens3 -> [TupleLens3]
TupleLens3 -> TupleLens3 -> TupleLens3 -> [TupleLens3]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TupleLens3 -> TupleLens3 -> TupleLens3 -> [TupleLens3]
$cenumFromThenTo :: TupleLens3 -> TupleLens3 -> TupleLens3 -> [TupleLens3]
enumFromTo :: TupleLens3 -> TupleLens3 -> [TupleLens3]
$cenumFromTo :: TupleLens3 -> TupleLens3 -> [TupleLens3]
enumFromThen :: TupleLens3 -> TupleLens3 -> [TupleLens3]
$cenumFromThen :: TupleLens3 -> TupleLens3 -> [TupleLens3]
enumFrom :: TupleLens3 -> [TupleLens3]
$cenumFrom :: TupleLens3 -> [TupleLens3]
fromEnum :: TupleLens3 -> Int
$cfromEnum :: TupleLens3 -> Int
toEnum :: Int -> TupleLens3
$ctoEnum :: Int -> TupleLens3
pred :: TupleLens3 -> TupleLens3
$cpred :: TupleLens3 -> TupleLens3
succ :: TupleLens3 -> TupleLens3
$csucc :: TupleLens3 -> TupleLens3
Enum, TupleLens3 -> TupleLens3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TupleLens3 -> TupleLens3 -> Bool
$c/= :: TupleLens3 -> TupleLens3 -> Bool
== :: TupleLens3 -> TupleLens3 -> Bool
$c== :: TupleLens3 -> TupleLens3 -> Bool
Eq, Eq TupleLens3
TupleLens3 -> TupleLens3 -> Bool
TupleLens3 -> TupleLens3 -> Ordering
TupleLens3 -> TupleLens3 -> TupleLens3
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
min :: TupleLens3 -> TupleLens3 -> TupleLens3
$cmin :: TupleLens3 -> TupleLens3 -> TupleLens3
max :: TupleLens3 -> TupleLens3 -> TupleLens3
$cmax :: TupleLens3 -> TupleLens3 -> TupleLens3
>= :: TupleLens3 -> TupleLens3 -> Bool
$c>= :: TupleLens3 -> TupleLens3 -> Bool
> :: TupleLens3 -> TupleLens3 -> Bool
$c> :: TupleLens3 -> TupleLens3 -> Bool
<= :: TupleLens3 -> TupleLens3 -> Bool
$c<= :: TupleLens3 -> TupleLens3 -> Bool
< :: TupleLens3 -> TupleLens3 -> Bool
$c< :: TupleLens3 -> TupleLens3 -> Bool
compare :: TupleLens3 -> TupleLens3 -> Ordering
$ccompare :: TupleLens3 -> TupleLens3 -> Ordering
Ord, Int -> TupleLens3 -> ShowS
[TupleLens3] -> ShowS
TupleLens3 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TupleLens3] -> ShowS
$cshowList :: [TupleLens3] -> ShowS
show :: TupleLens3 -> String
$cshow :: TupleLens3 -> String
showsPrec :: Int -> TupleLens3 -> ShowS
$cshowsPrec :: Int -> TupleLens3 -> ShowS
Show)
evalTupleLens3 :: (s, s, s) -> TupleLens3 -> s
evalTupleLens3 :: forall s. (s, s, s) -> TupleLens3 -> s
evalTupleLens3 (s
a, s
b, s
c) = \case
TupleLens3
TupleLens3A -> s
a
TupleLens3
TupleLens3B -> s
b
TupleLens3
TupleLens3C -> s
c
newtype Combination3 = Combination3 (NonEmpty TupleLens3)
deriving (Combination3 -> Combination3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Combination3 -> Combination3 -> Bool
$c/= :: Combination3 -> Combination3 -> Bool
== :: Combination3 -> Combination3 -> Bool
$c== :: Combination3 -> Combination3 -> Bool
Eq, Eq Combination3
Combination3 -> Combination3 -> Bool
Combination3 -> Combination3 -> Ordering
Combination3 -> Combination3 -> Combination3
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
min :: Combination3 -> Combination3 -> Combination3
$cmin :: Combination3 -> Combination3 -> Combination3
max :: Combination3 -> Combination3 -> Combination3
$cmax :: Combination3 -> Combination3 -> Combination3
>= :: Combination3 -> Combination3 -> Bool
$c>= :: Combination3 -> Combination3 -> Bool
> :: Combination3 -> Combination3 -> Bool
$c> :: Combination3 -> Combination3 -> Bool
<= :: Combination3 -> Combination3 -> Bool
$c<= :: Combination3 -> Combination3 -> Bool
< :: Combination3 -> Combination3 -> Bool
$c< :: Combination3 -> Combination3 -> Bool
compare :: Combination3 -> Combination3 -> Ordering
$ccompare :: Combination3 -> Combination3 -> Ordering
Ord, Int -> Combination3 -> ShowS
[Combination3] -> ShowS
Combination3 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Combination3] -> ShowS
$cshowList :: [Combination3] -> ShowS
show :: Combination3 -> String
$cshow :: Combination3 -> String
showsPrec :: Int -> Combination3 -> ShowS
$cshowsPrec :: Int -> Combination3 -> ShowS
Show)
arbitraryCombination3 :: Gen Combination3
arbitraryCombination3 :: Gen Combination3
arbitraryCombination3 =
NonEmpty TupleLens3 -> Combination3
Combination3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [TupleLens3]
arbitraryTupleLensList forall a b. Gen a -> (a -> Maybe b) -> Gen b
`suchThatMap` forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty
where
arbitraryTupleLensList :: Gen [TupleLens3]
arbitraryTupleLensList :: Gen [TupleLens3]
arbitraryTupleLensList = do
Int
itemCount <- forall a. Random a => (a, a) -> Gen a
choose (Int
1, Int
3)
forall a. Int -> [a] -> [a]
take Int
itemCount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [a] -> Gen [a]
shuffle forall a. (Bounded a, Enum a) => [a]
universe
evalCombination3 :: (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 :: forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
tuple (Combination3 NonEmpty TupleLens3
selectors) =
forall s. (s, s, s) -> TupleLens3 -> s
evalTupleLens3 (s, s, s)
tuple forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty TupleLens3
selectors
showCombination3 :: Show s => (s, s, s) -> Combination3 -> String
showCombination3 :: forall s. Show s => (s, s, s) -> Combination3 -> String
showCombination3 (s, s, s)
tuple =
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
m -> (a -> m) -> t a -> m
F1.intercalateMap1 String
" <> " forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
tuple
data Tuple1 s = Tuple1 Combination3 (s, s, s)
deriving (Tuple1 s -> Tuple1 s -> Bool
forall s. Eq s => Tuple1 s -> Tuple1 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tuple1 s -> Tuple1 s -> Bool
$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
Eq, Tuple1 s -> Tuple1 s -> Bool
Tuple1 s -> Tuple1 s -> Ordering
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
min :: Tuple1 s -> Tuple1 s -> Tuple1 s
$cmin :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Tuple1 s
max :: Tuple1 s -> Tuple1 s -> Tuple1 s
$cmax :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Tuple1 s
>= :: 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
$c< :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Bool
compare :: Tuple1 s -> Tuple1 s -> Ordering
$ccompare :: forall s. Ord s => Tuple1 s -> Tuple1 s -> Ordering
Ord)
data Tuple2 s = Tuple2 Combination3 Combination3 (s, s, s)
deriving (Tuple2 s -> Tuple2 s -> Bool
forall s. Eq s => Tuple2 s -> Tuple2 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tuple2 s -> Tuple2 s -> Bool
$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
Eq, Tuple2 s -> Tuple2 s -> Bool
Tuple2 s -> Tuple2 s -> Ordering
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
min :: Tuple2 s -> Tuple2 s -> Tuple2 s
$cmin :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Tuple2 s
max :: Tuple2 s -> Tuple2 s -> Tuple2 s
$cmax :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Tuple2 s
>= :: 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
$c< :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Bool
compare :: Tuple2 s -> Tuple2 s -> Ordering
$ccompare :: forall s. Ord s => Tuple2 s -> Tuple2 s -> Ordering
Ord)
data Tuple3 s = Tuple3 Combination3 Combination3 Combination3 (s, s, s)
deriving (Tuple3 s -> Tuple3 s -> Bool
forall s. Eq s => Tuple3 s -> Tuple3 s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tuple3 s -> Tuple3 s -> Bool
$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
Eq, Tuple3 s -> Tuple3 s -> Bool
Tuple3 s -> Tuple3 s -> Ordering
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
min :: Tuple3 s -> Tuple3 s -> Tuple3 s
$cmin :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Tuple3 s
max :: Tuple3 s -> Tuple3 s -> Tuple3 s
$cmax :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Tuple3 s
>= :: 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
$c< :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Bool
compare :: Tuple3 s -> Tuple3 s -> Ordering
$ccompare :: forall s. Ord s => Tuple3 s -> Tuple3 s -> Ordering
Ord)
instance Arbitrary a => Arbitrary (Tuple1 a) where
arbitrary :: Gen (Tuple1 a)
arbitrary = forall a. Arbitrary a => Gen (Tuple1 a)
arbitraryTuple1
shrink :: Tuple1 a -> [Tuple1 a]
shrink = forall a. Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1
instance Arbitrary a => Arbitrary (Tuple2 a) where
arbitrary :: Gen (Tuple2 a)
arbitrary = forall a. Arbitrary a => Gen (Tuple2 a)
arbitraryTuple2
shrink :: Tuple2 a -> [Tuple2 a]
shrink = forall a. Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2
instance Arbitrary a => Arbitrary (Tuple3 a) where
arbitrary :: Gen (Tuple3 a)
arbitrary = forall a. Arbitrary a => Gen (Tuple3 a)
arbitraryTuple3
shrink :: Tuple3 a -> [Tuple3 a]
shrink = forall a. Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3
instance (Show s, Semigroup s) => Show (Tuple1 s) where
show :: Tuple1 s -> String
show = forall a. (Semigroup a, Show a) => Tuple1 a -> String
showTuple1
instance (Show s, Semigroup s) => Show (Tuple2 s) where
show :: Tuple2 s -> String
show = forall a. (Semigroup a, Show a) => Tuple2 a -> String
showTuple2
instance (Show s, Semigroup s) => Show (Tuple3 s) where
show :: Tuple3 s -> String
show = forall a. (Semigroup a, Show a) => Tuple3 a -> String
showTuple3
arbitraryTuple1 :: Arbitrary a => Gen (Tuple1 a)
arbitraryTuple1 :: forall a. Arbitrary a => Gen (Tuple1 a)
arbitraryTuple1 = forall s. Combination3 -> (s, s, s) -> Tuple1 s
Tuple1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
arbitraryTuple2 :: Arbitrary a => Gen (Tuple2 a)
arbitraryTuple2 :: forall a. Arbitrary a => Gen (Tuple2 a)
arbitraryTuple2 = forall s. Combination3 -> Combination3 -> (s, s, s) -> Tuple2 s
Tuple2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
arbitraryTuple3 :: Arbitrary a => Gen (Tuple3 a)
arbitraryTuple3 :: forall a. Arbitrary a => Gen (Tuple3 a)
arbitraryTuple3 = forall s.
Combination3
-> Combination3 -> Combination3 -> (s, s, s) -> Tuple3 s
Tuple3
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Combination3
arbitraryCombination3
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
evalTuple1 :: Semigroup s => Tuple1 s -> s
evalTuple1 :: forall s. Semigroup s => Tuple1 s -> s
evalTuple1 (Tuple1 Combination3
c1 (s, s, s)
t) =
( forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c1
)
evalTuple2 :: Semigroup s => Tuple2 s -> (s, s)
evalTuple2 :: forall s. Semigroup s => Tuple2 s -> (s, s)
evalTuple2 (Tuple2 Combination3
c1 Combination3
c2 (s, s, s)
t) =
( forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c1
, forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c2
)
evalTuple3 :: Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 :: forall s. Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 (Tuple3 Combination3
c1 Combination3
c2 Combination3
c3 (s, s, s)
t) =
( forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c1
, forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c2
, forall (t :: * -> *) m. (Foldable1 t, Semigroup m) => t m -> m
F1.fold1 forall a b. (a -> b) -> a -> b
$ forall s. (s, s, s) -> Combination3 -> NonEmpty s
evalCombination3 (s, s, s)
t Combination3
c3
)
showTuple1 :: (Semigroup a, Show a) => Tuple1 a -> String
showTuple1 :: forall a. (Semigroup a, Show a) => Tuple1 a -> String
showTuple1 (forall s. Semigroup s => Tuple1 s -> s
evalTuple1 -> a
a) = [String] -> String
unlines
[ forall a. Monoid a => a
mempty, String
"a:", forall a. Show a => a -> String
showWrap a
a
]
showTuple2 :: (Semigroup a, Show a) => Tuple2 a -> String
showTuple2 :: forall a. (Semigroup a, Show a) => Tuple2 a -> String
showTuple2 (forall s. Semigroup s => Tuple2 s -> (s, s)
evalTuple2 -> (a
a, a
b)) = [String] -> String
unlines
[ forall a. Monoid a => a
mempty, String
"a:", forall a. Show a => a -> String
showWrap a
a
, forall a. Monoid a => a
mempty, String
"b:", forall a. Show a => a -> String
showWrap a
b
]
showTuple3 :: (Semigroup a, Show a) => Tuple3 a -> String
showTuple3 :: forall a. (Semigroup a, Show a) => Tuple3 a -> String
showTuple3 (forall s. Semigroup s => Tuple3 s -> (s, s, s)
evalTuple3 -> (a
a, a
b, a
c)) = [String] -> String
unlines
[ forall a. Monoid a => a
mempty, String
"a:", forall a. Show a => a -> String
showWrap a
a
, forall a. Monoid a => a
mempty, String
"b:", forall a. Show a => a -> String
showWrap a
b
, forall a. Monoid a => a
mempty, String
"c:", forall a. Show a => a -> String
showWrap a
c
]
shrinkTuple1 :: Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1 :: forall a. Arbitrary a => Tuple1 a -> [Tuple1 a]
shrinkTuple1 (Tuple1 Combination3
c1 (a, a, a)
t) = forall s. Combination3 -> (s, s, s) -> Tuple1 s
Tuple1 Combination3
c1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => a -> [a]
shrink (a, a, a)
t
shrinkTuple2 :: Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2 :: forall a. Arbitrary a => Tuple2 a -> [Tuple2 a]
shrinkTuple2 (Tuple2 Combination3
c1 Combination3
c2 (a, a, a)
t) = forall s. Combination3 -> Combination3 -> (s, s, s) -> Tuple2 s
Tuple2 Combination3
c1 Combination3
c2 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => a -> [a]
shrink (a, a, a)
t
shrinkTuple3 :: Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3 :: forall a. Arbitrary a => Tuple3 a -> [Tuple3 a]
shrinkTuple3 (Tuple3 Combination3
c1 Combination3
c2 Combination3
c3 (a, a, a)
t) = forall s.
Combination3
-> Combination3 -> Combination3 -> (s, s, s) -> Tuple3 s
Tuple3 Combination3
c1 Combination3
c2 Combination3
c3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => a -> [a]
shrink (a, a, 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 = forall a. Show a => a -> String
ppShow a
x
singleLine :: String
singleLine = forall a. Show a => a -> String
show a
x
singleLineMaxLength :: Int
singleLineMaxLength = Int
80
singleLineMaxLengthExceeded :: Bool
singleLineMaxLengthExceeded = forall (t :: * -> *) a. Foldable t => t a -> Int
F.length String
singleLine forall a. Ord a => a -> a -> Bool
> Int
singleLineMaxLength
universe :: (Bounded a, Enum a) => [a]
universe :: forall a. (Bounded a, Enum a) => [a]
universe = [forall a. Bounded a => a
minBound .. forall a. Bounded a => a
maxBound]