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

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

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

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

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

-- | @since 0.1.5
instance (Eq a, Eq b, Eq c) => Eq1 (T4 a b c) where
  liftEq :: forall a b. (a -> b -> Bool) -> T4 a b c a -> T4 a b c 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) => Eq2 (T4 a b) where
  liftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> T4 a b a c -> T4 a b b d -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
e2 (T4 a
a b
b a
c c
d) (T4 a
a' b
b' b
c' d
d') =
    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
&& a -> b -> Bool
e1 a
c b
c' Bool -> Bool -> Bool
&& c -> d -> Bool
e2 c
d d
d'

-- | @since 0.1.3
instance (Monoid a, Monoid b, Monoid c) => Applicative (T4 a b c) where
  pure :: forall a. a -> T4 a b c a
pure a
d = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty a
d
  T4 a
a b
b c
c a -> b
f <*> :: forall a b. T4 a b c (a -> b) -> T4 a b c a -> T4 a b c b
<*> T4 a
a' b
b' c
c' a
d = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 (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') (a -> b
f a
d)

-- | @since 0.1.3
instance (Monoid a, Monoid b, Monoid c) => Monad (T4 a b c) where
  return :: forall a. a -> T4 a b c a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
  T4 a
a b
b c
c a
d >>= :: forall a b. T4 a b c a -> (a -> T4 a b c b) -> T4 a b c b
>>= a -> T4 a b c b
f = case a -> T4 a b c b
f a
d of
    T4 a
a' b
b' c
c' b
d' -> forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 (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') b
d'

instance (Hashable a, Hashable b, Hashable c, Hashable d) => Hashable (T4 a b c d) where
  hash :: T4 a b c d -> Int
hash (T4 a
a b
b c
c d
d) = 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
  hashWithSalt :: Int -> T4 a b c d -> Int
hashWithSalt = forall (f :: * -> *) a.
(Hashable1 f, Hashable a) =>
Int -> f a -> Int
hashWithSalt1

instance (Hashable a, Hashable b, Hashable c) => Hashable1 (T4 a b c) where
  liftHashWithSalt :: forall a. (Int -> a -> Int) -> Int -> T4 a b c 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) => Hashable2 (T4 a b) where
  liftHashWithSalt2 :: forall a b.
(Int -> a -> Int) -> (Int -> b -> Int) -> Int -> T4 a b a b -> Int
liftHashWithSalt2 Int -> a -> Int
h1 Int -> b -> Int
h2 Int
slt (T4 a
a b
b a
c b
d) =
    (Int
slt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` a
a forall a. Hashable a => Int -> a -> Int
`hashWithSalt` b
b) Int -> a -> Int
`h1` a
c Int -> b -> Int
`h2` b
d

instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (T4 a b c d) where
  mempty :: T4 a b c d
mempty = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 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 (T4 a b c d) where
  rnf :: T4 a b c d -> ()
rnf (T4 a
a b
b c
c d
d) = 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

instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (T4 a b c d) where
  T4 a
a1 b
b1 c
c1 d
d1 <> :: T4 a b c d -> T4 a b c d -> T4 a b c d
<> T4 a
a2 b
b2 c
c2 d
d2 = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 (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)
  stimes :: forall b. Integral b => b -> T4 a b c d -> T4 a b c d
stimes b
ii (T4 a
a b
b c
c d
d) = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 (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)

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

-- | @since 0.1.3
instance Bifoldable (T4 x y) where
  bifoldMap :: forall m a b. Monoid m => (a -> m) -> (b -> m) -> T4 x y a b -> m
bifoldMap a -> m
f b -> m
g (T4 x
_ y
_ 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 (T4 x y) where
  bitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> T4 x y a b -> f (T4 x y c d)
bitraverse a -> f c
f b -> f d
g (T4 x
x y
y a
a b
b) = forall a b c d. a -> b -> c -> d -> T4 a b c d
T4 x
x y
y 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