module Data.List.Infinite.Zip (
zip,
zipWith,
zip3,
zipWith3,
zip4,
zipWith4,
zip5,
zipWith5,
zip6,
zipWith6,
zip7,
zipWith7,
) where
import Prelude (flip, (.))
import Data.List.Infinite.Internal
zip :: Infinite a -> Infinite b -> Infinite (a, b)
zip :: forall a b. Infinite a -> Infinite b -> Infinite (a, b)
zip = forall a b c.
(a -> b -> c) -> Infinite a -> Infinite b -> Infinite c
zipWith (,)
{-# INLINE zip #-}
zipWith :: (a -> b -> c) -> Infinite a -> Infinite b -> Infinite c
zipWith :: forall a b c.
(a -> b -> c) -> Infinite a -> Infinite b -> Infinite c
zipWith a -> b -> c
fun = Infinite a -> Infinite b -> Infinite c
go
where
go :: Infinite a -> Infinite b -> Infinite c
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) = a -> b -> c
fun a
a b
b forall a. a -> Infinite a -> Infinite a
:< Infinite a -> Infinite b -> Infinite c
go Infinite a
as Infinite b
bs
zipWithFB :: (elt -> lst -> lst') -> (a -> b -> elt) -> a -> b -> lst -> lst'
zipWithFB :: forall elt lst lst' a b.
(elt -> lst -> lst') -> (a -> b -> elt) -> a -> b -> lst -> lst'
zipWithFB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith #-}
{-# INLINE [0] zipWithFB #-}
{-# RULES
"zipWith" [~1] forall f xs ys.
zipWith f xs ys =
build (\cons -> foldr2 (zipWithFB cons f) xs ys)
"zipWithList" [1] forall f.
foldr2 (zipWithFB (:<) f) =
zipWith f
#-}
foldr2 :: (elt1 -> elt2 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> lst
foldr2 :: forall elt1 elt2 lst.
(elt1 -> elt2 -> lst -> lst)
-> Infinite elt1 -> Infinite elt2 -> lst
foldr2 elt1 -> elt2 -> lst -> lst
cons = Infinite elt1 -> Infinite elt2 -> lst
go
where
go :: Infinite elt1 -> Infinite elt2 -> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) = elt1 -> elt2 -> lst -> lst
cons elt1
a elt2
b (Infinite elt1 -> Infinite elt2 -> lst
go Infinite elt1
as Infinite elt2
bs)
{-# INLINE [0] foldr2 #-}
foldr2_left :: (elt1 -> elt2 -> lst -> lst') -> elt1 -> (Infinite elt2 -> lst) -> Infinite elt2 -> lst'
foldr2_left :: forall elt1 elt2 lst lst'.
(elt1 -> elt2 -> lst -> lst')
-> elt1 -> (Infinite elt2 -> lst) -> Infinite elt2 -> lst'
foldr2_left elt1 -> elt2 -> lst -> lst'
cons elt1
a Infinite elt2 -> lst
r (elt2
b :< Infinite elt2
bs) = elt1 -> elt2 -> lst -> lst'
cons elt1
a elt2
b (Infinite elt2 -> lst
r Infinite elt2
bs)
{-# RULES
"foldr2/1" forall (cons :: elt1 -> elt2 -> lst -> lst) (bs :: Infinite elt2) (g :: forall b. (elt1 -> b -> b) -> b).
foldr2 cons (build g) bs =
g (foldr2_left cons) bs
"foldr2/2" forall (cons :: elt1 -> elt2 -> lst -> lst) (as :: Infinite elt1) (g :: forall b. (elt2 -> b -> b) -> b).
foldr2 cons as (build g) =
g (foldr2_left (flip cons)) as
#-}
zip3 :: Infinite a -> Infinite b -> Infinite c -> Infinite (a, b, c)
zip3 :: forall a b c.
Infinite a -> Infinite b -> Infinite c -> Infinite (a, b, c)
zip3 = forall a b c d.
(a -> b -> c -> d)
-> Infinite a -> Infinite b -> Infinite c -> Infinite d
zipWith3 (,,)
{-# INLINE zip3 #-}
zipWith3 :: (a -> b -> c -> d) -> Infinite a -> Infinite b -> Infinite c -> Infinite d
zipWith3 :: forall a b c d.
(a -> b -> c -> d)
-> Infinite a -> Infinite b -> Infinite c -> Infinite d
zipWith3 a -> b -> c -> d
fun = Infinite a -> Infinite b -> Infinite c -> Infinite d
go
where
go :: Infinite a -> Infinite b -> Infinite c -> Infinite d
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) (c
c :< Infinite c
cs) = a -> b -> c -> d
fun a
a b
b c
c forall a. a -> Infinite a -> Infinite a
:< Infinite a -> Infinite b -> Infinite c -> Infinite d
go Infinite a
as Infinite b
bs Infinite c
cs
zipWith3FB :: (elt -> lst -> lst') -> (a -> b -> c -> elt) -> a -> b -> c -> lst -> lst'
zipWith3FB :: forall elt lst lst' a b c.
(elt -> lst -> lst')
-> (a -> b -> c -> elt) -> a -> b -> c -> lst -> lst'
zipWith3FB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith3 #-}
{-# INLINE [0] zipWith3FB #-}
{-# RULES
"zipWith3" [~1] forall f xs ys zs.
zipWith3 f xs ys zs =
build (\cons -> foldr3 (zipWith3FB cons f) xs ys zs)
"zipWith3List" [1] forall f.
foldr3 (zipWith3FB (:<) f) =
zipWith3 f
#-}
foldr3 :: (elt1 -> elt2 -> elt3 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> lst
foldr3 :: forall elt1 elt2 elt3 lst.
(elt1 -> elt2 -> elt3 -> lst -> lst)
-> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> lst
foldr3 elt1 -> elt2 -> elt3 -> lst -> lst
cons = Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> lst
go
where
go :: Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) = elt1 -> elt2 -> elt3 -> lst -> lst
cons elt1
a elt2
b elt3
c (Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> lst
go Infinite elt1
as Infinite elt2
bs Infinite elt3
cs)
{-# INLINE [0] foldr3 #-}
foldr3_left :: (elt1 -> elt2 -> elt3 -> lst -> lst') -> elt1 -> (Infinite elt2 -> Infinite elt3 -> lst) -> Infinite elt2 -> Infinite elt3 -> lst'
foldr3_left :: forall elt1 elt2 elt3 lst lst'.
(elt1 -> elt2 -> elt3 -> lst -> lst')
-> elt1
-> (Infinite elt2 -> Infinite elt3 -> lst)
-> Infinite elt2
-> Infinite elt3
-> lst'
foldr3_left elt1 -> elt2 -> elt3 -> lst -> lst'
cons elt1
a Infinite elt2 -> Infinite elt3 -> lst
r (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) = elt1 -> elt2 -> elt3 -> lst -> lst'
cons elt1
a elt2
b elt3
c (Infinite elt2 -> Infinite elt3 -> lst
r Infinite elt2
bs Infinite elt3
cs)
{-# RULES
"foldr3/1" forall (cons :: elt1 -> elt2 -> elt3 -> lst -> lst) (bs :: Infinite elt2) (cs :: Infinite elt3) (g :: forall b. (elt1 -> b -> b) -> b).
foldr3 cons (build g) bs cs =
g (foldr3_left cons) bs cs
"foldr3/2" forall (cons :: elt1 -> elt2 -> elt3 -> lst -> lst) (as :: Infinite elt1) (cs :: Infinite elt3) (g :: forall b. (elt2 -> b -> b) -> b).
foldr3 cons as (build g) cs =
g (foldr3_left (flip cons)) as cs
"foldr3/3" forall (cons :: elt1 -> elt2 -> elt3 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (g :: forall b. (elt3 -> b -> b) -> b).
foldr3 cons as bs (build g) =
g (foldr3_left (\c a b -> cons a b c)) as bs
#-}
zip4 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite (a, b, c, d)
zip4 :: forall a b c d.
Infinite a
-> Infinite b -> Infinite c -> Infinite d -> Infinite (a, b, c, d)
zip4 = forall a b c d e.
(a -> b -> c -> d -> e)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
zipWith4 (,,,)
{-# INLINE zip4 #-}
zipWith4 :: (a -> b -> c -> d -> e) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e
zipWith4 :: forall a b c d e.
(a -> b -> c -> d -> e)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
zipWith4 a -> b -> c -> d -> e
fun = Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e
go
where
go :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) (c
c :< Infinite c
cs) (d
d :< Infinite d
ds) = a -> b -> c -> d -> e
fun a
a b
b c
c d
d forall a. a -> Infinite a -> Infinite a
:< Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e
go Infinite a
as Infinite b
bs Infinite c
cs Infinite d
ds
zipWith4FB :: (elt -> lst -> lst') -> (a -> b -> c -> d -> elt) -> a -> b -> c -> d -> lst -> lst'
zipWith4FB :: forall elt lst lst' a b c d.
(elt -> lst -> lst')
-> (a -> b -> c -> d -> elt) -> a -> b -> c -> d -> lst -> lst'
zipWith4FB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith4 #-}
{-# INLINE [0] zipWith4FB #-}
{-# RULES
"zipWith4" [~1] forall f xs ys zs ts.
zipWith4 f xs ys zs ts =
build (\cons -> foldr4 (zipWith4FB cons f) xs ys zs ts)
"zipWith4List" [1] forall f.
foldr4 (zipWith4FB (:<) f) =
zipWith4 f
#-}
foldr4 :: (elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
foldr4 :: forall elt1 elt2 elt3 elt4 lst.
(elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst)
-> Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> lst
foldr4 elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst
cons = Infinite elt1
-> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
go
where
go :: Infinite elt1
-> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) = elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst
cons elt1
a elt2
b elt3
c elt4
d (Infinite elt1
-> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
go Infinite elt1
as Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds)
{-# INLINE [0] foldr4 #-}
foldr4_left :: (elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst') -> elt1 -> (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst) -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst'
foldr4_left :: forall elt1 elt2 elt3 elt4 lst lst'.
(elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst')
-> elt1
-> (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst)
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> lst'
foldr4_left elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst'
cons elt1
a Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
r (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) = elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst'
cons elt1
a elt2
b elt3
c elt4
d (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> lst
r Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds)
{-# RULES
"foldr4/1" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (g :: forall b. (elt1 -> b -> b) -> b).
foldr4 cons (build g) bs cs ds =
g (foldr4_left cons) bs cs ds
"foldr4/2" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst) (as :: Infinite elt1) (cs :: Infinite elt3) (ds :: Infinite elt4) (g :: forall b. (elt2 -> b -> b) -> b).
foldr4 cons as (build g) cs ds =
g (foldr4_left (flip cons)) as cs ds
"foldr4/3" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (ds :: Infinite elt4) (g :: forall b. (elt3 -> b -> b) -> b).
foldr4 cons as bs (build g) ds =
g (foldr4_left (\c a b d -> cons a b c d)) as bs ds
"foldr4/4" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (g :: forall b. (elt4 -> b -> b) -> b).
foldr4 cons as bs cs (build g) =
g (foldr4_left (\d a b c -> cons a b c d)) as bs cs
#-}
zip5 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite (a, b, c, d, e)
zip5 :: forall a b c d e.
Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite (a, b, c, d, e)
zip5 = forall a b c d e f.
(a -> b -> c -> d -> e -> f)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
zipWith5 (,,,,)
{-# INLINE zip5 #-}
zipWith5 :: (a -> b -> c -> d -> e -> f) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f
zipWith5 :: forall a b c d e f.
(a -> b -> c -> d -> e -> f)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
zipWith5 a -> b -> c -> d -> e -> f
fun = Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
go
where
go :: Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) (c
c :< Infinite c
cs) (d
d :< Infinite d
ds) (e
e :< Infinite e
es) = a -> b -> c -> d -> e -> f
fun a
a b
b c
c d
d e
e forall a. a -> Infinite a -> Infinite a
:< Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
go Infinite a
as Infinite b
bs Infinite c
cs Infinite d
ds Infinite e
es
zipWith5FB :: (elt -> lst -> lst') -> (a -> b -> c -> d -> e -> elt) -> a -> b -> c -> d -> e -> lst -> lst'
zipWith5FB :: forall elt lst lst' a b c d e.
(elt -> lst -> lst')
-> (a -> b -> c -> d -> e -> elt)
-> a
-> b
-> c
-> d
-> e
-> lst
-> lst'
zipWith5FB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith5 #-}
{-# INLINE [0] zipWith5FB #-}
{-# RULES
"zipWith5" [~1] forall f xs ys zs ts us.
zipWith5 f xs ys zs ts us =
build (\cons -> foldr5 (zipWith5FB cons f) xs ys zs ts us)
"zipWith5List" [1] forall f.
foldr5 (zipWith5FB (:<) f) =
zipWith5 f
#-}
foldr5 :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst
foldr5 :: forall elt1 elt2 elt3 elt4 elt5 lst.
(elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst)
-> Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> lst
foldr5 elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst
cons = Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> lst
go
where
go :: Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst
cons elt1
a elt2
b elt3
c elt4
d elt5
e (Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> lst
go Infinite elt1
as Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es)
{-# INLINE [0] foldr5 #-}
foldr5_left :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst') -> elt1 -> (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst) -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst'
foldr5_left :: forall elt1 elt2 elt3 elt4 elt5 lst lst'.
(elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst')
-> elt1
-> (Infinite elt2
-> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst)
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> lst'
foldr5_left elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst'
cons elt1
a Infinite elt2
-> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst
r (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst'
cons elt1
a elt2
b elt3
c elt4
d elt5
e (Infinite elt2
-> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> lst
r Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es)
{-# RULES
"foldr5/1" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (g :: forall b. (elt1 -> b -> b) -> b).
foldr5 cons (build g) bs cs ds es =
g (foldr5_left cons) bs cs ds es
"foldr5/2" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) (as :: Infinite elt1) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (g :: forall b. (elt2 -> b -> b) -> b).
foldr5 cons as (build g) cs ds es =
g (foldr5_left (flip cons)) as cs ds es
"foldr5/3" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (ds :: Infinite elt4) (es :: Infinite elt5) (g :: forall b. (elt3 -> b -> b) -> b).
foldr5 cons as bs (build g) ds es =
g (foldr5_left (\c a b d e -> cons a b c d e)) as bs ds es
"foldr5/4" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (es :: Infinite elt5) (g :: forall b. (elt4 -> b -> b) -> b).
foldr5 cons as bs cs (build g) es =
g (foldr5_left (\d a b c e -> cons a b c d e)) as bs cs es
"foldr5/5" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (g :: forall b. (elt5 -> b -> b) -> b).
foldr5 cons as bs cs ds (build g) =
g (foldr5_left (\e a b c d -> cons a b c d e)) as bs cs ds
#-}
zip6 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite (a, b, c, d, e, f)
zip6 :: forall a b c d e f.
Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite (a, b, c, d, e, f)
zip6 = forall a b c d e f g.
(a -> b -> c -> d -> e -> f -> g)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
zipWith6 (,,,,,)
{-# INLINE zip6 #-}
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g
zipWith6 :: forall a b c d e f g.
(a -> b -> c -> d -> e -> f -> g)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
zipWith6 a -> b -> c -> d -> e -> f -> g
fun = Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
go
where
go :: Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) (c
c :< Infinite c
cs) (d
d :< Infinite d
ds) (e
e :< Infinite e
es) (f
f :< Infinite f
fs) = a -> b -> c -> d -> e -> f -> g
fun a
a b
b c
c d
d e
e f
f forall a. a -> Infinite a -> Infinite a
:< Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
go Infinite a
as Infinite b
bs Infinite c
cs Infinite d
ds Infinite e
es Infinite f
fs
zipWith6FB :: (elt -> lst -> lst') -> (a -> b -> c -> d -> e -> f -> elt) -> a -> b -> c -> d -> e -> f -> lst -> lst'
zipWith6FB :: forall elt lst lst' a b c d e f.
(elt -> lst -> lst')
-> (a -> b -> c -> d -> e -> f -> elt)
-> a
-> b
-> c
-> d
-> e
-> f
-> lst
-> lst'
zipWith6FB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith6 #-}
{-# INLINE [0] zipWith6FB #-}
{-# RULES
"zipWith6" [~1] forall f xs ys zs ts us vs.
zipWith6 f xs ys zs ts us vs =
build (\cons -> foldr6 (zipWith6FB cons f) xs ys zs ts us vs)
"zipWith6List" [1] forall f.
foldr6 (zipWith6FB (:<) f) =
zipWith6 f
#-}
foldr6 :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> lst
foldr6 :: forall elt1 elt2 elt3 elt4 elt5 elt6 lst.
(elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst)
-> Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
foldr6 elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst
cons = Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
go
where
go :: Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) (elt6
f :< Infinite elt6
fs) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst
cons elt1
a elt2
b elt3
c elt4
d elt5
e elt6
f (Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
go Infinite elt1
as Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es Infinite elt6
fs)
{-# INLINE [0] foldr6 #-}
foldr6_left :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst') -> elt1 -> (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> lst) -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> lst'
foldr6_left :: forall elt1 elt2 elt3 elt4 elt5 elt6 lst lst'.
(elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst')
-> elt1
-> (Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst)
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst'
foldr6_left elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst'
cons elt1
a Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
r (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) (elt6
f :< Infinite elt6
fs) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst'
cons elt1
a elt2
b elt3
c elt4
d elt5
e elt6
f (Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> lst
r Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es Infinite elt6
fs)
{-# RULES
"foldr6/1" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (g :: forall b. (elt1 -> b -> b) -> b).
foldr6 cons (build g) bs cs ds es fs =
g (foldr6_left cons) bs cs ds es fs
"foldr6/2" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (as :: Infinite elt1) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (g :: forall b. (elt2 -> b -> b) -> b).
foldr6 cons as (build g) cs ds es fs =
g (foldr6_left (flip cons)) as cs ds es fs
"foldr6/3" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (g :: forall b. (elt3 -> b -> b) -> b).
foldr6 cons as bs (build g) ds es fs =
g (foldr6_left (\c a b d e f -> cons a b c d e f)) as bs ds es fs
"foldr6/4" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (es :: Infinite elt5) (fs :: Infinite elt6) (g :: forall b. (elt4 -> b -> b) -> b).
foldr6 cons as bs cs (build g) es fs =
g (foldr6_left (\d a b c e f -> cons a b c d e f)) as bs cs es fs
"foldr6/5" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (fs :: Infinite elt6) (g :: forall b. (elt5 -> b -> b) -> b).
foldr6 cons as bs cs ds (build g) fs =
g (foldr6_left (\e a b c d f -> cons a b c d e f)) as bs cs ds fs
"foldr6/6" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (g :: forall b. (elt6 -> b -> b) -> b).
foldr6 cons as bs cs ds es (build g) =
g (foldr6_left (\f a b c d e -> cons a b c d e f)) as bs cs ds es
#-}
zip7 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite (a, b, c, d, e, f, g)
zip7 :: forall a b c d e f g.
Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite (a, b, c, d, e, f, g)
zip7 = forall a b c d e f g h.
(a -> b -> c -> d -> e -> f -> g -> h)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite h
zipWith7 (,,,,,,)
{-# INLINE zip7 #-}
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite h
zipWith7 :: forall a b c d e f g h.
(a -> b -> c -> d -> e -> f -> g -> h)
-> Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite h
zipWith7 a -> b -> c -> d -> e -> f -> g -> h
fun = Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite h
go
where
go :: Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite h
go (a
a :< Infinite a
as) (b
b :< Infinite b
bs) (c
c :< Infinite c
cs) (d
d :< Infinite d
ds) (e
e :< Infinite e
es) (f
f :< Infinite f
fs) (g
g :< Infinite g
gs) = a -> b -> c -> d -> e -> f -> g -> h
fun a
a b
b c
c d
d e
e f
f g
g forall a. a -> Infinite a -> Infinite a
:< Infinite a
-> Infinite b
-> Infinite c
-> Infinite d
-> Infinite e
-> Infinite f
-> Infinite g
-> Infinite h
go Infinite a
as Infinite b
bs Infinite c
cs Infinite d
ds Infinite e
es Infinite f
fs Infinite g
gs
zipWith7FB :: (elt -> lst -> lst') -> (a -> b -> c -> d -> e -> f -> g -> elt) -> a -> b -> c -> d -> e -> f -> g -> lst -> lst'
zipWith7FB :: forall elt lst lst' a b c d e f g.
(elt -> lst -> lst')
-> (a -> b -> c -> d -> e -> f -> g -> elt)
-> a
-> b
-> c
-> d
-> e
-> f
-> g
-> lst
-> lst'
zipWith7FB = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
{-# NOINLINE [1] zipWith7 #-}
{-# INLINE [0] zipWith7FB #-}
{-# RULES
"zipWith7" [~1] forall f xs ys zs ts us vs ws.
zipWith7 f xs ys zs ts us vs ws =
build (\cons -> foldr7 (zipWith7FB cons f) xs ys zs ts us vs ws)
"zipWith7List" [1] forall f.
foldr7 (zipWith7FB (:<) f) =
zipWith7 f
#-}
foldr7 :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) -> Infinite elt1 -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> Infinite elt7 -> lst
foldr7 :: forall elt1 elt2 elt3 elt4 elt5 elt6 elt7 lst.
(elt1
-> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst)
-> Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
foldr7 elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst
cons = Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
go
where
go :: Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
go (elt1
a :< Infinite elt1
as) (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) (elt6
f :< Infinite elt6
fs) (elt7
g :< Infinite elt7
gs) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst
cons elt1
a elt2
b elt3
c elt4
d elt5
e elt6
f elt7
g (Infinite elt1
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
go Infinite elt1
as Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es Infinite elt6
fs Infinite elt7
gs)
{-# INLINE [0] foldr7 #-}
foldr7_left :: (elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst') -> elt1 -> (Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> Infinite elt7 -> lst) -> Infinite elt2 -> Infinite elt3 -> Infinite elt4 -> Infinite elt5 -> Infinite elt6 -> Infinite elt7 -> lst'
foldr7_left :: forall elt1 elt2 elt3 elt4 elt5 elt6 elt7 lst lst'.
(elt1
-> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst')
-> elt1
-> (Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst)
-> Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst'
foldr7_left elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst'
cons elt1
a Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
r (elt2
b :< Infinite elt2
bs) (elt3
c :< Infinite elt3
cs) (elt4
d :< Infinite elt4
ds) (elt5
e :< Infinite elt5
es) (elt6
f :< Infinite elt6
fs) (elt7
g :< Infinite elt7
gs) = elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst'
cons elt1
a elt2
b elt3
c elt4
d elt5
e elt6
f elt7
g (Infinite elt2
-> Infinite elt3
-> Infinite elt4
-> Infinite elt5
-> Infinite elt6
-> Infinite elt7
-> lst
r Infinite elt2
bs Infinite elt3
cs Infinite elt4
ds Infinite elt5
es Infinite elt6
fs Infinite elt7
gs)
{-# RULES
"foldr7/1" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (gs :: Infinite elt7) (g :: forall b. (elt1 -> b -> b) -> b).
foldr7 cons (build g) bs cs ds es fs gs =
g (foldr7_left cons) bs cs ds es fs gs
"foldr7/2" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (gs :: Infinite elt7) (g :: forall b. (elt2 -> b -> b) -> b).
foldr7 cons as (build g) cs ds es fs gs =
g (foldr7_left (flip cons)) as cs ds es fs gs
"foldr7/3" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (gs :: Infinite elt7) (g :: forall b. (elt3 -> b -> b) -> b).
foldr7 cons as bs (build g) ds es fs gs =
g (foldr7_left (\c a b d e f g' -> cons a b c d e f g')) as bs ds es fs gs
"foldr7/4" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (es :: Infinite elt5) (fs :: Infinite elt6) (gs :: Infinite elt7) (g :: forall b. (elt4 -> b -> b) -> b).
foldr7 cons as bs cs (build g) es fs gs =
g (foldr7_left (\d a b c e f g' -> cons a b c d e f g')) as bs cs es fs gs
"foldr7/5" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (fs :: Infinite elt6) (gs :: Infinite elt7) (g :: forall b. (elt5 -> b -> b) -> b).
foldr7 cons as bs cs ds (build g) fs gs =
g (foldr7_left (\e a b c d f g' -> cons a b c d e f g')) as bs cs ds fs gs
"foldr7/6" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (gs :: Infinite elt7) (g :: forall b. (elt6 -> b -> b) -> b).
foldr7 cons as bs cs ds es (build g) gs =
g (foldr7_left (\f a b c d e g' -> cons a b c d e f g')) as bs cs ds es gs
"foldr7/7" forall (cons :: elt1 -> elt2 -> elt3 -> elt4 -> elt5 -> elt6 -> elt7 -> lst -> lst) (as :: Infinite elt1) (bs :: Infinite elt2) (cs :: Infinite elt3) (ds :: Infinite elt4) (es :: Infinite elt5) (fs :: Infinite elt6) (g :: forall b. (elt7 -> b -> b) -> b).
foldr7 cons as bs cs ds es fs (build g) =
g (foldr7_left (\g' a b c d e f -> cons a b c d e f g')) as bs cs ds es fs
#-}