{-# LANGUAGE CPP #-}
module Test.LeanCheck.Basic
( module Test.LeanCheck.Core
, cons6
, cons7
, cons8
, cons9
, cons10
, cons11
, cons12
, ofWeight
, addWeight
)
where
import Test.LeanCheck.Core
import Data.Ratio
import Data.Complex
import Data.Int
import Data.Word
import Data.Char (GeneralCategory)
import System.IO (IOMode (..), BufferMode (..), SeekMode (..))
import Foreign.C
import System.Exit
instance (Listable a, Listable b, Listable c,
Listable d, Listable e, Listable f) =>
Listable (a,b,c,d,e,f) where
tiers :: [[(a, b, c, d, e, f)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u) -> (a
x,b
y,c
z,d
w,e
v,f
u)) forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g) =>
Listable (a,b,c,d,e,f,g) where
tiers :: [[(a, b, c, d, e, f, g)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r) -> (a
x,b
y,c
z,d
w,e
v,f
u,g
r)) forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h) =>
Listable (a,b,c,d,e,f,g,h) where
tiers :: [[(a, b, c, d, e, f, g, h)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r,h
s) -> (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s)) forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i) =>
Listable (a,b,c,d,e,f,g,h,i) where
tiers :: [[(a, b, c, d, e, f, g, h, i)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t) -> (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t))
forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i, Listable j) =>
Listable (a,b,c,d,e,f,g,h,i,j) where
tiers :: [[(a, b, c, d, e, f, g, h, i, j)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o) -> (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o))
forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h,
Listable i, Listable j, Listable k) =>
Listable (a,b,c,d,e,f,g,h,i,j,k) where
tiers :: [[(a, b, c, d, e, f, g, h, i, j, k)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p) -> (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p))
forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
instance (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h,
Listable i, Listable j, Listable k, Listable l) =>
Listable (a,b,c,d,e,f,g,h,i,j,k,l) where
tiers :: [[(a, b, c, d, e, f, g, h, i, j, k, l)]]
tiers = forall a b c. (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
productWith (\a
x (b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p,l
q) ->
(a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p,l
q))
forall a. Listable a => [[a]]
tiers forall a. Listable a => [[a]]
tiers
cons6 :: (Listable a, Listable b, Listable c,
Listable d, Listable e, Listable f)
=> (a -> b -> c -> d -> e -> f -> g) -> [[g]]
cons6 :: forall a b c d e f g.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f) =>
(a -> b -> c -> d -> e -> f -> g) -> [[g]]
cons6 a -> b -> c -> d -> e -> f -> g
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g.
(a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
uncurry6 a -> b -> c -> d -> e -> f -> g
f) forall a. Listable a => [[a]]
tiers
cons7 :: (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g)
=> (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]]
cons7 :: forall a b c d e f g h.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g) =>
(a -> b -> c -> d -> e -> f -> g -> h) -> [[h]]
cons7 a -> b -> c -> d -> e -> f -> g -> h
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h.
(a -> b -> c -> d -> e -> f -> g -> h)
-> (a, b, c, d, e, f, g) -> h
uncurry7 a -> b -> c -> d -> e -> f -> g -> h
f) forall a. Listable a => [[a]]
tiers
cons8 :: (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h)
=> (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [[i]]
cons8 :: forall a b c d e f g h i.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h) =>
(a -> b -> c -> d -> e -> f -> g -> h -> i) -> [[i]]
cons8 a -> b -> c -> d -> e -> f -> g -> h -> i
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h i.
(a -> b -> c -> d -> e -> f -> g -> h -> i)
-> (a, b, c, d, e, f, g, h) -> i
uncurry8 a -> b -> c -> d -> e -> f -> g -> h -> i
f) forall a. Listable a => [[a]]
tiers
cons9 :: (Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i)
=> (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [[j]]
cons9 :: forall a b c d e f g h i j.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i) =>
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [[j]]
cons9 a -> b -> c -> d -> e -> f -> g -> h -> i -> j
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h i j.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j)
-> (a, b, c, d, e, f, g, h, i) -> j
uncurry9 a -> b -> c -> d -> e -> f -> g -> h -> i -> j
f) forall a. Listable a => [[a]]
tiers
cons10 :: (Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i, Listable j)
=> (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [[k]]
cons10 :: forall a b c d e f g h i j k.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i, Listable j) =>
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [[k]]
cons10 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h i j k.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k)
-> (a, b, c, d, e, f, g, h, i, j) -> k
uncurry10 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
f) forall a. Listable a => [[a]]
tiers
cons11 :: (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h,
Listable i, Listable j, Listable k)
=> (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [[l]]
cons11 :: forall a b c d e f g h i j k l.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i, Listable j,
Listable k) =>
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [[l]]
cons11 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h i j k l.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l)
-> (a, b, c, d, e, f, g, h, i, j, k) -> l
uncurry11 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l
f) forall a. Listable a => [[a]]
tiers
cons12 :: (Listable a, Listable b, Listable c, Listable d,
Listable e, Listable f, Listable g, Listable h,
Listable i, Listable j, Listable k, Listable l)
=> (a->b->c->d->e->f->g->h->i->j->k->l->m) -> [[m]]
cons12 :: forall a b c d e f g h i j k l m.
(Listable a, Listable b, Listable c, Listable d, Listable e,
Listable f, Listable g, Listable h, Listable i, Listable j,
Listable k, Listable l) =>
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m)
-> [[m]]
cons12 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m
f = forall a. [[a]] -> [[a]]
delay forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (forall a b c d e f g h i j k l m.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m)
-> (a, b, c, d, e, f, g, h, i, j, k, l) -> m
uncurry12 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m
f) forall a. Listable a => [[a]]
tiers
uncurry6 :: (a->b->c->d->e->f->g) -> (a,b,c,d,e,f) -> g
uncurry6 :: forall a b c d e f g.
(a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
uncurry6 a -> b -> c -> d -> e -> f -> g
f (a
x,b
y,c
z,d
w,e
v,f
u) = a -> b -> c -> d -> e -> f -> g
f a
x b
y c
z d
w e
v f
u
uncurry7 :: (a->b->c->d->e->f->g->h) -> (a,b,c,d,e,f,g) -> h
uncurry7 :: forall a b c d e f g h.
(a -> b -> c -> d -> e -> f -> g -> h)
-> (a, b, c, d, e, f, g) -> h
uncurry7 a -> b -> c -> d -> e -> f -> g -> h
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r) = a -> b -> c -> d -> e -> f -> g -> h
f a
x b
y c
z d
w e
v f
u g
r
uncurry8 :: (a->b->c->d->e->f->g->h->i) -> (a,b,c,d,e,f,g,h) -> i
uncurry8 :: forall a b c d e f g h i.
(a -> b -> c -> d -> e -> f -> g -> h -> i)
-> (a, b, c, d, e, f, g, h) -> i
uncurry8 a -> b -> c -> d -> e -> f -> g -> h -> i
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s) = a -> b -> c -> d -> e -> f -> g -> h -> i
f a
x b
y c
z d
w e
v f
u g
r h
s
uncurry9 :: (a->b->c->d->e->f->g->h->i->j) -> (a,b,c,d,e,f,g,h,i) -> j
uncurry9 :: forall a b c d e f g h i j.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j)
-> (a, b, c, d, e, f, g, h, i) -> j
uncurry9 a -> b -> c -> d -> e -> f -> g -> h -> i -> j
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t) = a -> b -> c -> d -> e -> f -> g -> h -> i -> j
f a
x b
y c
z d
w e
v f
u g
r h
s i
t
uncurry10 :: (a->b->c->d->e->f->g->h->i->j->k) -> (a,b,c,d,e,f,g,h,i,j) -> k
uncurry10 :: forall a b c d e f g h i j k.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k)
-> (a, b, c, d, e, f, g, h, i, j) -> k
uncurry10 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o) = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
f a
x b
y c
z d
w e
v f
u g
r h
s i
t j
o
uncurry11 :: (a->b->c->d->e->f->g->h->i->j->k->l)
-> (a,b,c,d,e,f,g,h,i,j,k) -> l
uncurry11 :: forall a b c d e f g h i j k l.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l)
-> (a, b, c, d, e, f, g, h, i, j, k) -> l
uncurry11 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p) = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l
f a
x b
y c
z d
w e
v f
u g
r h
s i
t j
o k
p
uncurry12 :: (a->b->c->d->e->f->g->h->i->j->k->l->m)
-> (a,b,c,d,e,f,g,h,i,j,k,l) -> m
uncurry12 :: forall a b c d e f g h i j k l m.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m)
-> (a, b, c, d, e, f, g, h, i, j, k, l) -> m
uncurry12 a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m
f (a
x,b
y,c
z,d
w,e
v,f
u,g
r,h
s,i
t,j
o,k
p,l
q) = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m
f a
x b
y c
z d
w e
v f
u g
r h
s i
t j
o k
p l
q
instance (Integral a, Listable a) => Listable (Ratio a) where
list :: [Ratio a]
list = forall a. (Ord a, Fractional a) => [a]
listFractional
instance (RealFloat a, Listable a) => Listable (Complex a) where
tiers :: [[Complex a]]
tiers = forall a b c. (Listable a, Listable b) => (a -> b -> c) -> [[c]]
cons2 forall a. a -> a -> Complex a
(:+)
instance Listable Word where
list :: [Word]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Word8 where
list :: [Word8]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Word16 where
list :: [Word16]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Word32 where
list :: [Word32]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Word64 where
list :: [Word64]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Int8 where
list :: [Int8]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Int16 where
list :: [Int16]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Int32 where
list :: [Int32]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable Int64 where
list :: [Int64]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CChar where list :: [CChar]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CSChar where list :: [CSChar]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CUChar where list :: [CUChar]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CShort where list :: [CShort]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CUShort where list :: [CUShort]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CInt where list :: [CInt]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CUInt where list :: [CUInt]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CLong where list :: [CLong]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CULong where list :: [CULong]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CPtrdiff where list :: [CPtrdiff]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CSize where list :: [CSize]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CWchar where list :: [CWchar]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CSigAtomic where list :: [CSigAtomic]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CLLong where list :: [CLLong]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CULLong where list :: [CULLong]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CIntPtr where list :: [CIntPtr]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CUIntPtr where list :: [CUIntPtr]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CIntMax where list :: [CIntMax]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CUIntMax where list :: [CUIntMax]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CClock where list :: [CClock]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CTime where list :: [CTime]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CFloat where list :: [CFloat]
list = forall a. (Ord a, Fractional a) => [a]
listFloating
instance Listable CDouble where list :: [CDouble]
list = forall a. (Ord a, Fractional a) => [a]
listFloating
#if __GLASGOW_HASKELL__ >= 802
instance Listable CBool where list :: [CBool]
list = forall a. (Ord a, Num a) => [a]
listIntegral
#endif
#if __GLASGOW_HASKELL__
instance Listable CUSeconds where list :: [CUSeconds]
list = forall a. (Ord a, Num a) => [a]
listIntegral
instance Listable CSUSeconds where list :: [CSUSeconds]
list = forall a. (Ord a, Num a) => [a]
listIntegral
#endif
instance Listable ExitCode where
list :: [ExitCode]
list = ExitCode
ExitSuccess forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map Int -> ExitCode
ExitFailure [Int
1..Int
255]
instance Listable GeneralCategory where list :: [GeneralCategory]
list = [forall a. Bounded a => a
minBound..forall a. Bounded a => a
maxBound]
instance Listable IOMode where
tiers :: [[IOMode]]
tiers = forall a. a -> [[a]]
cons0 IOMode
ReadMode
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 IOMode
WriteMode
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 IOMode
AppendMode
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 IOMode
ReadWriteMode
instance Listable BufferMode where
tiers :: [[BufferMode]]
tiers = forall a. a -> [[a]]
cons0 BufferMode
NoBuffering
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 BufferMode
LineBuffering
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a b. Listable a => (a -> b) -> [[b]]
cons1 Maybe Int -> BufferMode
BlockBuffering
instance Listable SeekMode where
tiers :: [[SeekMode]]
tiers = forall a. a -> [[a]]
cons0 SeekMode
AbsoluteSeek
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 SeekMode
RelativeSeek
forall a. [[a]] -> [[a]] -> [[a]]
\/ forall a. a -> [[a]]
cons0 SeekMode
SeekFromEnd
ofWeight :: [[a]] -> Int -> [[a]]
ofWeight :: forall a. [[a]] -> Int -> [[a]]
ofWeight [[a]]
xss Int
w = forall a. (a -> Bool) -> [a] -> [a]
dropWhile forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[a]]
xss forall a. [[a]] -> Int -> [[a]]
`addWeight` Int
w
addWeight :: [[a]] -> Int -> [[a]]
addWeight :: forall a. [[a]] -> Int -> [[a]]
addWeight [[a]]
xss Int
w = forall a. Int -> a -> [a]
replicate Int
w [] forall a. [a] -> [a] -> [a]
++ [[a]]
xss