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

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

import Control.DeepSeq (NFData, rnf)
import Data.Bifoldable
import Data.Bifunctor
import Data.Bitraversable
import Data.Functor.Classes (Eq1 (liftEq), Eq2 (liftEq2))
import Data.Hashable (Hashable, hash, hashWithSalt)
import Data.Hashable.Lifted
  ( Hashable1,
    Hashable2,
    defaultLiftHashWithSalt,
    hashWithSalt1,
    liftHashWithSalt,
    liftHashWithSalt2,
  )
import Data.Semigroup
import GHC.Generics (Generic)

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

-- | @since 0.1.3
deriving stock instance Foldable (T5 a b c d)

-- | @since 0.1.3
deriving stock instance Functor (T5 a b c d)

-- | @since 0.1.3
deriving stock instance Traversable (T5 a b c d)

-- | @since 0.1.5
instance (Eq a, Eq b, Eq c, Eq d) => Eq1 (T5 a b c d) where
  liftEq :: forall a b.
(a -> b -> Bool) -> T5 a b c d a -> T5 a b c d b -> Bool
liftEq = forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 forall a. Eq a => a -> a -> Bool
(==)

-- | @since 0.1.5
instance (Eq a, Eq b, Eq c) => Eq2 (T5 a b c) where
  liftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> T5 a b c a c -> T5 a b c b d -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
e2 (T5 a
a b
b c
c a
d c
e) (T5 a
a' b
b' c
c' b
d' d
e') =
    a
a forall a. Eq a => a -> a -> Bool
== a
a' Bool -> Bool -> Bool
&& b
b forall a. Eq a => a -> a -> Bool
== b
b' Bool -> Bool -> Bool
&& c
c forall a. Eq a => a -> a -> Bool
== c
c' Bool -> Bool -> Bool
&& a -> b -> Bool
e1 a
d b
d' Bool -> Bool -> Bool
&& c -> d -> Bool
e2 c
e d
e'

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

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

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

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

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

instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (T5 a b c d e) where
  mempty :: T5 a b c d e
mempty = forall a b c d e. a -> b -> c -> d -> e -> T5 a b c d e
T5 forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

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

instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (T5 a b c d e) where
  T5 a
a1 b
b1 c
c1 d
d1 e
e1 <> :: T5 a b c d e -> T5 a b c d e -> T5 a b c d e
<> T5 a
a2 b
b2 c
c2 d
d2 e
e2 = forall a b c d e. a -> b -> c -> d -> e -> T5 a b c d e
T5 (a
a1 forall a. Semigroup a => a -> a -> a
<> a
a2) (b
b1 forall a. Semigroup a => a -> a -> a
<> b
b2) (c
c1 forall a. Semigroup a => a -> a -> a
<> c
c2) (d
d1 forall a. Semigroup a => a -> a -> a
<> d
d2) (e
e1 forall a. Semigroup a => a -> a -> a
<> e
e2)
  stimes :: forall b. Integral b => b -> T5 a b c d e -> T5 a b c d e
stimes b
ii (T5 a
a b
b c
c d
d e
e) = forall a b c d e. a -> b -> c -> d -> e -> T5 a b c d e
T5 (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii a
a) (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii b
b) (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii c
c) (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii d
d) (forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
ii e
e)

-- | @since 0.1.3
instance Bifunctor (T5 x y z) where
  bimap :: forall a b c d.
(a -> b) -> (c -> d) -> T5 x y z a c -> T5 x y z b d
bimap a -> b
f c -> d
g (T5 x
x y
y z
z a
a c
b) = forall a b c d e. a -> b -> c -> d -> e -> T5 a b c d e
T5 x
x y
y z
z (a -> b
f a
a) (c -> d
g c
b)

-- | @since 0.1.3
instance Bifoldable (T5 x y z) where
  bifoldMap :: forall m a b. Monoid m => (a -> m) -> (b -> m) -> T5 x y z a b -> m
bifoldMap a -> m
f b -> m
g (T5 x
_ y
_ z
_ a
a b
b) = a -> m
f a
a forall a. Semigroup a => a -> a -> a
<> b -> m
g b
b

-- | @since 0.1.3
instance Bitraversable (T5 x y z) where
  bitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> T5 x y z a b -> f (T5 x y z c d)
bitraverse a -> f c
f b -> f d
g (T5 x
x y
y z
z a
a b
b) = forall a b c d e. a -> b -> c -> d -> e -> T5 a b c d e
T5 x
x y
y z
z forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> f d
g b
b