{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}

module Data.Tuple.Strict.T9
  ( T9 (..),
  )
where

import Control.DeepSeq (NFData, rnf)
import Data.Biapplicative
import Data.Bifoldable
import Data.Bitraversable
import Data.Hashable (Hashable, hash, hashWithSalt)
import Data.Hashable.Lifted
  ( Hashable1,
    Hashable2,
    defaultLiftHashWithSalt,
    hashWithSalt1,
    liftHashWithSalt,
    liftHashWithSalt2,
  )
import Data.Semigroup
import GHC.Generics (Generic)

data T9 a b c d e f g h i
  = T9 a b c d e f g h i
  deriving stock (T9 a b c d e f g h i
T9 a b c d e f g h i
-> T9 a b c d e f g h i -> Bounded (T9 a b c d e f g h i)
forall a. a -> a -> Bounded a
forall a b c d e f g h i.
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f,
 Bounded g, Bounded h, Bounded i) =>
T9 a b c d e f g h i
maxBound :: T9 a b c d e f g h i
$cmaxBound :: forall a b c d e f g h i.
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f,
 Bounded g, Bounded h, Bounded i) =>
T9 a b c d e f g h i
minBound :: T9 a b c d e f g h i
$cminBound :: forall a b c d e f g h i.
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f,
 Bounded g, Bounded h, Bounded i) =>
T9 a b c d e f g h i
Bounded, T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
(T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> Eq (T9 a b c d e f g h i)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b c d e f g h i.
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
/= :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c/= :: forall a b c d e f g h i.
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
== :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c== :: forall a b c d e f g h i.
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
Eq, Eq (T9 a b c d e f g h i)
Eq (T9 a b c d e f g h i)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Ordering)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> (T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool)
-> (T9 a b c d e f g h i
    -> T9 a b c d e f g h i -> T9 a b c d e f g h i)
-> (T9 a b c d e f g h i
    -> T9 a b c d e f g h i -> T9 a b c d e f g h i)
-> Ord (T9 a b c d e f g h i)
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Ordering
T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
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 a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
Eq (T9 a b c d e f g h i)
forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Ordering
forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
min :: T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
$cmin :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
max :: T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
$cmax :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
>= :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c>= :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
> :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c> :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
<= :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c<= :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
< :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
$c< :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Bool
compare :: T9 a b c d e f g h i -> T9 a b c d e f g h i -> Ordering
$ccompare :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
T9 a b c d e f g h i -> T9 a b c d e f g h i -> Ordering
$cp1Ord :: forall a b c d e f g h i.
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) =>
Eq (T9 a b c d e f g h i)
Ord, ReadPrec [T9 a b c d e f g h i]
ReadPrec (T9 a b c d e f g h i)
Int -> ReadS (T9 a b c d e f g h i)
ReadS [T9 a b c d e f g h i]
(Int -> ReadS (T9 a b c d e f g h i))
-> ReadS [T9 a b c d e f g h i]
-> ReadPrec (T9 a b c d e f g h i)
-> ReadPrec [T9 a b c d e f g h i]
-> Read (T9 a b c d e f g h i)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadPrec [T9 a b c d e f g h i]
forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadPrec (T9 a b c d e f g h i)
forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
Int -> ReadS (T9 a b c d e f g h i)
forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadS [T9 a b c d e f g h i]
readListPrec :: ReadPrec [T9 a b c d e f g h i]
$creadListPrec :: forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadPrec [T9 a b c d e f g h i]
readPrec :: ReadPrec (T9 a b c d e f g h i)
$creadPrec :: forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadPrec (T9 a b c d e f g h i)
readList :: ReadS [T9 a b c d e f g h i]
$creadList :: forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
ReadS [T9 a b c d e f g h i]
readsPrec :: Int -> ReadS (T9 a b c d e f g h i)
$creadsPrec :: forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
 Read i) =>
Int -> ReadS (T9 a b c d e f g h i)
Read, Int -> T9 a b c d e f g h i -> ShowS
[T9 a b c d e f g h i] -> ShowS
T9 a b c d e f g h i -> String
(Int -> T9 a b c d e f g h i -> ShowS)
-> (T9 a b c d e f g h i -> String)
-> ([T9 a b c d e f g h i] -> ShowS)
-> Show (T9 a b c d e f g h i)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
Int -> T9 a b c d e f g h i -> ShowS
forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
[T9 a b c d e f g h i] -> ShowS
forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
T9 a b c d e f g h i -> String
showList :: [T9 a b c d e f g h i] -> ShowS
$cshowList :: forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
[T9 a b c d e f g h i] -> ShowS
show :: T9 a b c d e f g h i -> String
$cshow :: forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
T9 a b c d e f g h i -> String
showsPrec :: Int -> T9 a b c d e f g h i -> ShowS
$cshowsPrec :: forall a b c d e f g h i.
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h,
 Show i) =>
Int -> T9 a b c d e f g h i -> ShowS
Show, (forall x. T9 a b c d e f g h i -> Rep (T9 a b c d e f g h i) x)
-> (forall x. Rep (T9 a b c d e f g h i) x -> T9 a b c d e f g h i)
-> Generic (T9 a b c d e f g h i)
forall x. Rep (T9 a b c d e f g h i) x -> T9 a b c d e f g h i
forall x. T9 a b c d e f g h i -> Rep (T9 a b c d e f g h i) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b c d e f g h i x.
Rep (T9 a b c d e f g h i) x -> T9 a b c d e f g h i
forall a b c d e f g h i x.
T9 a b c d e f g h i -> Rep (T9 a b c d e f g h i) x
$cto :: forall a b c d e f g h i x.
Rep (T9 a b c d e f g h i) x -> T9 a b c d e f g h i
$cfrom :: forall a b c d e f g h i x.
T9 a b c d e f g h i -> Rep (T9 a b c d e f g h i) x
Generic)

-- | @since 0.1.3
deriving stock instance Foldable (T9 a b c d e f g h)

-- | @since 0.1.3
deriving stock instance Functor (T9 a b c d e f g h)

-- | @since 0.1.3
deriving stock instance Traversable (T9 a b c d e f g h)

-- | @since 0.1.3
instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e, Monoid f, Monoid g, Monoid h) => Applicative (T9 a b c d e f g h) where
  pure :: a -> T9 a b c d e f g h a
pure a
i = a -> b -> c -> d -> e -> f -> g -> h -> a -> T9 a b c d e f g h a
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 a
forall a. Monoid a => a
mempty b
forall a. Monoid a => a
mempty c
forall a. Monoid a => a
mempty d
forall a. Monoid a => a
mempty e
forall a. Monoid a => a
mempty f
forall a. Monoid a => a
mempty g
forall a. Monoid a => a
mempty h
forall a. Monoid a => a
mempty a
i
  T9 a
a b
b c
c d
d e
e f
f g
g h
h a -> b
i <*> :: T9 a b c d e f g h (a -> b)
-> T9 a b c d e f g h a -> T9 a b c d e f g h b
<*> T9 a
a' b
b' c
c' d
d' e
e' f
f' g
g' h
h' a
i' =
    a -> b -> c -> d -> e -> f -> g -> h -> b -> T9 a b c d e f g h b
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a') (b
b b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b') (c
c c -> c -> c
forall a. Semigroup a => a -> a -> a
<> c
c') (d
d d -> d -> d
forall a. Semigroup a => a -> a -> a
<> d
d') (e
e e -> e -> e
forall a. Semigroup a => a -> a -> a
<> e
e') (f
f f -> f -> f
forall a. Semigroup a => a -> a -> a
<> f
f') (g
g g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
g') (h
h h -> h -> h
forall a. Semigroup a => a -> a -> a
<> h
h') (a -> b
i a
i')

-- | @since 0.1.3
instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e, Monoid f, Monoid g, Monoid h) => Monad (T9 a b c d e f g h) where
  return :: a -> T9 a b c d e f g h a
return = a -> T9 a b c d e f g h a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
  T9 a
a b
b c
c d
d e
e f
f g
g h
h a
i >>= :: T9 a b c d e f g h a
-> (a -> T9 a b c d e f g h b) -> T9 a b c d e f g h b
>>= a -> T9 a b c d e f g h b
j = case a -> T9 a b c d e f g h b
j a
i of
    T9 a
a' b
b' c
c' d
d' e
e' f
f' g
g' h
h' b
i' ->
      a -> b -> c -> d -> e -> f -> g -> h -> b -> T9 a b c d e f g h b
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a') (b
b b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b') (c
c c -> c -> c
forall a. Semigroup a => a -> a -> a
<> c
c') (d
d d -> d -> d
forall a. Semigroup a => a -> a -> a
<> d
d') (e
e e -> e -> e
forall a. Semigroup a => a -> a -> a
<> e
e') (f
f f -> f -> f
forall a. Semigroup a => a -> a -> a
<> f
f') (g
g g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
g') (h
h h -> h -> h
forall a. Semigroup a => a -> a -> a
<> h
h') b
i'

instance (Hashable a, Hashable b, Hashable c, Hashable d, Hashable e, Hashable f, Hashable g, Hashable h, Hashable i) => Hashable (T9 a b c d e f g h i) where
  hash :: T9 a b c d e f g h i -> Int
hash (T9 a
a b
b c
c d
d e
e f
f g
g h
h i
i) = a -> Int
forall a. Hashable a => a -> Int
hash a
a Int -> b -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` b
b Int -> c -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` c
c Int -> d -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` d
d Int -> e -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` e
e Int -> f -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` f
f Int -> g -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` g
g Int -> h -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` h
h Int -> i -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` i
i
  hashWithSalt :: Int -> T9 a b c d e f g h i -> Int
hashWithSalt = Int -> T9 a b c d e f g h i -> Int
forall (f :: * -> *) a.
(Hashable1 f, Hashable a) =>
Int -> f a -> Int
hashWithSalt1

instance (Hashable a, Hashable b, Hashable c, Hashable d, Hashable e, Hashable f, Hashable g, Hashable h) => Hashable1 (T9 a b c d e f g h) where
  liftHashWithSalt :: (Int -> a -> Int) -> Int -> T9 a b c d e f g h a -> Int
liftHashWithSalt = (Int -> a -> Int) -> Int -> T9 a b c d e f g h a -> Int
forall (f :: * -> * -> *) a b.
(Hashable2 f, Hashable a) =>
(Int -> b -> Int) -> Int -> f a b -> Int
defaultLiftHashWithSalt

instance (Hashable a, Hashable b, Hashable c, Hashable d, Hashable e, Hashable f, Hashable g) => Hashable2 (T9 a b c d e f g) where
  liftHashWithSalt2 :: (Int -> a -> Int)
-> (Int -> b -> Int) -> Int -> T9 a b c d e f g a b -> Int
liftHashWithSalt2 Int -> a -> Int
h1 Int -> b -> Int
h2 Int
slt (T9 a
a b
b c
c d
d e
e f
f g
g a
h b
i) =
    (Int
slt Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` a
a Int -> b -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` b
b Int -> c -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` c
c Int -> d -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` d
d Int -> e -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` e
e Int -> f -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` f
f Int -> g -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` g
g) Int -> a -> Int
`h1` a
h Int -> b -> Int
`h2` b
i

instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e, Monoid f, Monoid g, Monoid h, Monoid i) => Monoid (T9 a b c d e f g h i) where
  mempty :: T9 a b c d e f g h i
mempty = a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 a
forall a. Monoid a => a
mempty b
forall a. Monoid a => a
mempty c
forall a. Monoid a => a
mempty d
forall a. Monoid a => a
mempty e
forall a. Monoid a => a
mempty f
forall a. Monoid a => a
mempty g
forall a. Monoid a => a
mempty h
forall a. Monoid a => a
mempty i
forall a. Monoid a => a
mempty

-- | @since 0.1.4
instance (NFData a, NFData b, NFData c, NFData d, NFData e, NFData f, NFData g, NFData h, NFData i) => NFData (T9 a b c d e f g h i) where
  rnf :: T9 a b c d e f g h i -> ()
rnf (T9 a
a b
b c
c d
d e
e f
f g
g h
h i
i) = a -> ()
forall a. NFData a => a -> ()
rnf a
a () -> () -> ()
`seq` b -> ()
forall a. NFData a => a -> ()
rnf b
b () -> () -> ()
`seq` c -> ()
forall a. NFData a => a -> ()
rnf c
c () -> () -> ()
`seq` d -> ()
forall a. NFData a => a -> ()
rnf d
d () -> () -> ()
`seq` e -> ()
forall a. NFData a => a -> ()
rnf e
e () -> () -> ()
`seq` f -> ()
forall a. NFData a => a -> ()
rnf f
f () -> () -> ()
`seq` g -> ()
forall a. NFData a => a -> ()
rnf g
g () -> () -> ()
`seq` h -> ()
forall a. NFData a => a -> ()
rnf h
h () -> () -> ()
`seq` i -> ()
forall a. NFData a => a -> ()
rnf i
i

instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e, Semigroup f, Semigroup g, Semigroup h, Semigroup i) => Semigroup (T9 a b c d e f g h i) where
  T9 a
a1 b
b1 c
c1 d
d1 e
e1 f
f1 g
g1 h
h1 i
i1 <> :: T9 a b c d e f g h i
-> T9 a b c d e f g h i -> T9 a b c d e f g h i
<> T9 a
a2 b
b2 c
c2 d
d2 e
e2 f
f2 g
g2 h
h2 i
i2 = a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 (a
a1 a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a2) (b
b1 b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b2) (c
c1 c -> c -> c
forall a. Semigroup a => a -> a -> a
<> c
c2) (d
d1 d -> d -> d
forall a. Semigroup a => a -> a -> a
<> d
d2) (e
e1 e -> e -> e
forall a. Semigroup a => a -> a -> a
<> e
e2) (f
f1 f -> f -> f
forall a. Semigroup a => a -> a -> a
<> f
f2) (g
g1 g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
g2) (h
h1 h -> h -> h
forall a. Semigroup a => a -> a -> a
<> h
h2) (i
i1 i -> i -> i
forall a. Semigroup a => a -> a -> a
<> i
i2)
  stimes :: b -> T9 a b c d e f g h i -> T9 a b c d e f g h i
stimes b
ii (T9 a
a b
b c
c d
d e
e f
f g
g h
h i
i) = a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 (b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii a
a) (b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii b
b) (b -> c -> c
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii c
c) (b -> d -> d
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii d
d) (b -> e -> e
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii e
e) (b -> f -> f
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii f
f) (b -> g -> g
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii g
g) (b -> h -> h
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii h
h) (b -> i -> i
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii i
i)

-- | @since 0.1.3
instance Bifunctor (T9 x y z w t u v) where
  bimap :: (a -> b)
-> (c -> d) -> T9 x y z w t u v a c -> T9 x y z w t u v b d
bimap a -> b
f c -> d
g (T9 x
x y
y z
z w
w t
t u
u v
v a
a c
b) = x -> y -> z -> w -> t -> u -> v -> b -> d -> T9 x y z w t u v b d
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 x
x y
y z
z w
w t
t u
u v
v (a -> b
f a
a) (c -> d
g c
b)

-- | @since 0.1.3
instance Bifoldable (T9 x y z w t u v) where
  bifoldMap :: (a -> m) -> (b -> m) -> T9 x y z w t u v a b -> m
bifoldMap a -> m
f b -> m
g (T9 x
_ y
_ z
_ w
_ t
_ u
_ v
_ a
a b
b) = a -> m
f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> b -> m
g b
b

-- | @since 0.1.3
instance Bitraversable (T9 x y z w t u v) where
  bitraverse :: (a -> f c)
-> (b -> f d) -> T9 x y z w t u v a b -> f (T9 x y z w t u v c d)
bitraverse a -> f c
f b -> f d
g (T9 x
x y
y z
z w
w t
t u
u v
v a
a b
b) = x -> y -> z -> w -> t -> u -> v -> c -> d -> T9 x y z w t u v c d
forall a b c d e f g h i.
a -> b -> c -> d -> e -> f -> g -> h -> i -> T9 a b c d e f g h i
T9 x
x y
y z
z w
w t
t u
u v
v (c -> d -> T9 x y z w t u v c d)
-> f c -> f (d -> T9 x y z w t u v c d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
a f (d -> T9 x y z w t u v c d) -> f d -> f (T9 x y z w t u v c d)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> f d
g b
b