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

module Data.Tuple.Strict.T2
  ( T2 (..),
    sfst,
    ssnd,
    scurry,
    suncurry,
    sswap,
  )
where

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

-- | @since 0.1.3
deriving stock instance Foldable (T2 a)

-- | @since 0.1.3
deriving stock instance Functor (T2 a)

-- | @since 0.1.3
deriving stock instance Traversable (T2 a)

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

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

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

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

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

instance Hashable2 T2 where
  liftHashWithSalt2 :: forall a b.
(Int -> a -> Int) -> (Int -> b -> Int) -> Int -> T2 a b -> Int
liftHashWithSalt2 Int -> a -> Int
h1 Int -> b -> Int
h2 Int
slt (T2 a
a b
b) = Int
slt Int -> a -> Int
`h1` a
a Int -> b -> Int
`h2` b
b

instance (Monoid a, Monoid b) => Monoid (T2 a b) where
  mempty :: T2 a b
mempty = forall a b. a -> b -> T2 a b
T2 forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

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

instance (Semigroup a, Semigroup b) => Semigroup (T2 a b) where
  T2 a
a1 b
b1 <> :: T2 a b -> T2 a b -> T2 a b
<> T2 a
a2 b
b2 = forall a b. a -> b -> T2 a b
T2 (a
a1 forall a. Semigroup a => a -> a -> a
<> a
a2) (b
b1 forall a. Semigroup a => a -> a -> a
<> b
b2)
  stimes :: forall b. Integral b => b -> T2 a b -> T2 a b
stimes b
ii (T2 a
a b
b) = forall a b. a -> b -> T2 a b
T2 (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)

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

-- | @since 0.1.3
instance Biapplicative T2 where
  bipure :: forall a b. a -> b -> T2 a b
bipure = forall a b. a -> b -> T2 a b
T2
  T2 a -> b
f c -> d
g <<*>> :: forall a b c d. T2 (a -> b) (c -> d) -> T2 a c -> T2 b d
<<*>> T2 a
a c
b = forall a b. a -> b -> T2 a b
T2 (a -> b
f a
a) (c -> d
g c
b)

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

-- | A strict, 'T2'-based analog to 'fst'
--
-- @since 0.1.3
sfst :: T2 a b -> a
sfst :: forall a b. T2 a b -> a
sfst (T2 a
a b
_) = a
a

-- | A strict, 'T2'-based analog to 'snd'
--
-- @since 0.1.3
ssnd :: T2 a b -> b
ssnd :: forall a b. T2 a b -> b
ssnd (T2 a
_ b
b) = b
b

-- | A strict, 'T2'-based analog to 'curry'
--
-- @since 0.1.3
scurry :: (T2 a b -> c) -> a -> b -> c
scurry :: forall a b c. (T2 a b -> c) -> a -> b -> c
scurry T2 a b -> c
f a
a b
b = T2 a b -> c
f (forall a b. a -> b -> T2 a b
T2 a
a b
b)

-- | A strict, 'T2'-based analog to 'uncurry'
--
-- @since 0.1.3
suncurry :: (a -> b -> c) -> T2 a b -> c
suncurry :: forall a b c. (a -> b -> c) -> T2 a b -> c
suncurry a -> b -> c
f (T2 a
a b
b) = a -> b -> c
f a
a b
b

-- | A strict, 'T2'-based analog to 'swap'
--
-- @since 0.1.3
sswap :: T2 a b -> T2 b a
sswap :: forall a b. T2 a b -> T2 b a
sswap (T2 a
a b
b) = forall a b. a -> b -> T2 a b
T2 b
b a
a