{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable     #-}
{-# LANGUAGE DeriveFunctor      #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DeriveTraversable  #-}
{-# LANGUAGE FlexibleContexts   #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE Safe               #-}

#if MIN_VERSION_base(4,9,0)
#define LIFTED_FUNCTOR_CLASSES 1
#else
#if MIN_VERSION_transformers (0,5,0)
#define LIFTED_FUNCTOR_CLASSES 1
#else
#if MIN_VERSION_transformers_compat(0,5,0) && !MIN_VERSION_transformers(0,4,0)
#define LIFTED_FUNCTOR_CLASSES 1
#endif
#endif
#endif
module Data.Functor.These (
    These1 (..),
    ) where

import Data.Foldable        (Foldable)
import Data.Functor.Classes (Eq1 (..), Ord1 (..), Read1 (..), Show1 (..))
import Data.Monoid          (Monoid (..))
import Data.Semigroup       (Semigroup (..))
import Data.Traversable     (Traversable)
import GHC.Generics         (Generic)
import Prelude
       (Bool (..), Eq (..), Functor, Ord (..), Ordering (..), Read (..),
       Show (..), lex, readParen, return, seq, showChar, showParen, showString,
       ($), (&&), (.))

import qualified Data.Foldable  as F
import qualified Data.Foldable1 as F1

#if MIN_VERSION_deepseq(1,4,3)
import Control.DeepSeq (NFData (..), NFData1 (..))
#else
import Control.DeepSeq (NFData (..))
#endif

#if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
#endif

#if __GLASGOW_HASKELL__ >= 708
import Data.Data     (Data)
import Data.Typeable (Typeable)
#endif

-------------------------------------------------------------------------------
-- These1
-------------------------------------------------------------------------------

data These1 f g a
    = This1 (f a)
    | That1 (g a)
    | These1 (f a) (g a)
  deriving (forall a b. a -> These1 f g b -> These1 f g a
forall a b. (a -> b) -> These1 f g a -> These1 f g b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
a -> These1 f g b -> These1 f g a
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> These1 f g a -> These1 f g b
<$ :: forall a b. a -> These1 f g b -> These1 f g a
$c<$ :: forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
a -> These1 f g b -> These1 f g a
fmap :: forall a b. (a -> b) -> These1 f g a -> These1 f g b
$cfmap :: forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> These1 f g a -> These1 f g b
Functor, forall a. These1 f g a -> Bool
forall m a. Monoid m => (a -> m) -> These1 f g a -> m
forall a b. (a -> b -> b) -> b -> These1 f g a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Eq a) =>
a -> These1 f g a -> Bool
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
These1 f g a -> a
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
These1 f g a -> a
forall (f :: * -> *) (g :: * -> *) m.
(Foldable f, Foldable g, Monoid m) =>
These1 f g m -> m
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> Bool
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> Int
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> [a]
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> These1 f g a -> a
forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> These1 f g a -> m
forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> These1 f g a -> b
forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> These1 f g a -> b
product :: forall a. Num a => These1 f g a -> a
$cproduct :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
These1 f g a -> a
sum :: forall a. Num a => These1 f g a -> a
$csum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
These1 f g a -> a
minimum :: forall a. Ord a => These1 f g a -> a
$cminimum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
These1 f g a -> a
maximum :: forall a. Ord a => These1 f g a -> a
$cmaximum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
These1 f g a -> a
elem :: forall a. Eq a => a -> These1 f g a -> Bool
$celem :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Eq a) =>
a -> These1 f g a -> Bool
length :: forall a. These1 f g a -> Int
$clength :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> Int
null :: forall a. These1 f g a -> Bool
$cnull :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> Bool
toList :: forall a. These1 f g a -> [a]
$ctoList :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
These1 f g a -> [a]
foldl1 :: forall a. (a -> a -> a) -> These1 f g a -> a
$cfoldl1 :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> These1 f g a -> a
foldr1 :: forall a. (a -> a -> a) -> These1 f g a -> a
$cfoldr1 :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> These1 f g a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> These1 f g a -> b
$cfoldl' :: forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> These1 f g a -> b
foldl :: forall b a. (b -> a -> b) -> b -> These1 f g a -> b
$cfoldl :: forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> These1 f g a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> These1 f g a -> b
$cfoldr' :: forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> These1 f g a -> b
foldr :: forall a b. (a -> b -> b) -> b -> These1 f g a -> b
$cfoldr :: forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> These1 f g a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> These1 f g a -> m
$cfoldMap' :: forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> These1 f g a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> These1 f g a -> m
$cfoldMap :: forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> These1 f g a -> m
fold :: forall m. Monoid m => These1 f g m -> m
$cfold :: forall (f :: * -> *) (g :: * -> *) m.
(Foldable f, Foldable g, Monoid m) =>
These1 f g m -> m
Foldable, forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> These1 f g a -> f (These1 f g b)
forall {f :: * -> *} {g :: * -> *}.
(Traversable f, Traversable g) =>
Functor (These1 f g)
forall {f :: * -> *} {g :: * -> *}.
(Traversable f, Traversable g) =>
Foldable (These1 f g)
forall (f :: * -> *) (g :: * -> *) (m :: * -> *) a.
(Traversable f, Traversable g, Monad m) =>
These1 f g (m a) -> m (These1 f g a)
forall (f :: * -> *) (g :: * -> *) (f :: * -> *) a.
(Traversable f, Traversable g, Applicative f) =>
These1 f g (f a) -> f (These1 f g a)
forall (f :: * -> *) (g :: * -> *) (m :: * -> *) a b.
(Traversable f, Traversable g, Monad m) =>
(a -> m b) -> These1 f g a -> m (These1 f g b)
forall (f :: * -> *) (g :: * -> *) (f :: * -> *) a b.
(Traversable f, Traversable g, Applicative f) =>
(a -> f b) -> These1 f g a -> f (These1 f g b)
sequence :: forall (m :: * -> *) a.
Monad m =>
These1 f g (m a) -> m (These1 f g a)
$csequence :: forall (f :: * -> *) (g :: * -> *) (m :: * -> *) a.
(Traversable f, Traversable g, Monad m) =>
These1 f g (m a) -> m (These1 f g a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> These1 f g a -> m (These1 f g b)
$cmapM :: forall (f :: * -> *) (g :: * -> *) (m :: * -> *) a b.
(Traversable f, Traversable g, Monad m) =>
(a -> m b) -> These1 f g a -> m (These1 f g b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
These1 f g (f a) -> f (These1 f g a)
$csequenceA :: forall (f :: * -> *) (g :: * -> *) (f :: * -> *) a.
(Traversable f, Traversable g, Applicative f) =>
These1 f g (f a) -> f (These1 f g a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> These1 f g a -> f (These1 f g b)
$ctraverse :: forall (f :: * -> *) (g :: * -> *) (f :: * -> *) a b.
(Traversable f, Traversable g, Applicative f) =>
(a -> f b) -> These1 f g a -> f (These1 f g b)
Traversable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) (g :: * -> *) a x.
Rep (These1 f g a) x -> These1 f g a
forall (f :: * -> *) (g :: * -> *) a x.
These1 f g a -> Rep (These1 f g a) x
$cto :: forall (f :: * -> *) (g :: * -> *) a x.
Rep (These1 f g a) x -> These1 f g a
$cfrom :: forall (f :: * -> *) (g :: * -> *) a x.
These1 f g a -> Rep (These1 f g a) x
Generic
#if __GLASGOW_HASKELL__ >= 706
    , forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall (f :: * -> *) (g :: * -> *) a.
Rep1 (These1 f g) a -> These1 f g a
forall (f :: * -> *) (g :: * -> *) a.
These1 f g a -> Rep1 (These1 f g) a
$cto1 :: forall (f :: * -> *) (g :: * -> *) a.
Rep1 (These1 f g) a -> These1 f g a
$cfrom1 :: forall (f :: * -> *) (g :: * -> *) a.
These1 f g a -> Rep1 (These1 f g) a
Generic1
#endif
#if __GLASGOW_HASKELL__ >= 708
    , Typeable, These1 f g a -> DataType
These1 f g a -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (These1 f g a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> These1 f g a -> c (These1 f g a)
forall {f :: * -> *} {g :: * -> *} {a}.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
Typeable (These1 f g a)
forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
These1 f g a -> DataType
forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
These1 f g a -> Constr
forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall b. Data b => b -> b) -> These1 f g a -> These1 f g a
forall (f :: * -> *) (g :: * -> *) a u.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
Int -> (forall d. Data d => d -> u) -> These1 f g a -> u
forall (f :: * -> *) (g :: * -> *) a u.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall d. Data d => d -> u) -> These1 f g a -> [u]
forall (f :: * -> *) (g :: * -> *) a r r'.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
forall (f :: * -> *) (g :: * -> *) a r r'.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
forall (f :: * -> *) (g :: * -> *) a (m :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Monad m) =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
forall (f :: * -> *) (g :: * -> *) a (m :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 MonadPlus m) =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
forall (f :: * -> *) (g :: * -> *) a (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (These1 f g a)
forall (f :: * -> *) (g :: * -> *) a (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> These1 f g a -> c (These1 f g a)
forall (f :: * -> *) (g :: * -> *) a (t :: * -> *) (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (These1 f g a))
forall (f :: * -> *) (g :: * -> *) a (t :: * -> * -> *)
       (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (These1 f g a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
$cgmapMo :: forall (f :: * -> *) (g :: * -> *) a (m :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 MonadPlus m) =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
$cgmapMp :: forall (f :: * -> *) (g :: * -> *) a (m :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 MonadPlus m) =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
$cgmapM :: forall (f :: * -> *) (g :: * -> *) a (m :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Monad m) =>
(forall d. Data d => d -> m d) -> These1 f g a -> m (These1 f g a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> These1 f g a -> u
$cgmapQi :: forall (f :: * -> *) (g :: * -> *) a u.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
Int -> (forall d. Data d => d -> u) -> These1 f g a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> These1 f g a -> [u]
$cgmapQ :: forall (f :: * -> *) (g :: * -> *) a u.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall d. Data d => d -> u) -> These1 f g a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
$cgmapQr :: forall (f :: * -> *) (g :: * -> *) a r r'.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
$cgmapQl :: forall (f :: * -> *) (g :: * -> *) a r r'.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> These1 f g a -> r
gmapT :: (forall b. Data b => b -> b) -> These1 f g a -> These1 f g a
$cgmapT :: forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall b. Data b => b -> b) -> These1 f g a -> These1 f g a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (These1 f g a))
$cdataCast2 :: forall (f :: * -> *) (g :: * -> *) a (t :: * -> * -> *)
       (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (These1 f g a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (These1 f g a))
$cdataCast1 :: forall (f :: * -> *) (g :: * -> *) a (t :: * -> *) (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a),
 Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (These1 f g a))
dataTypeOf :: These1 f g a -> DataType
$cdataTypeOf :: forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
These1 f g a -> DataType
toConstr :: These1 f g a -> Constr
$ctoConstr :: forall (f :: * -> *) (g :: * -> *) a.
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
These1 f g a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (These1 f g a)
$cgunfold :: forall (f :: * -> *) (g :: * -> *) a (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (These1 f g a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> These1 f g a -> c (These1 f g a)
$cgfoldl :: forall (f :: * -> *) (g :: * -> *) a (c :: * -> *).
(Typeable f, Typeable g, Typeable a, Data (f a), Data (g a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> These1 f g a -> c (These1 f g a)
Data
#endif
    )

-------------------------------------------------------------------------------
-- Eq1
-------------------------------------------------------------------------------

instance (Eq1 f, Eq1 g) => Eq1 (These1 f g) where
#ifdef LIFTED_FUNCTOR_CLASSES
    liftEq :: forall a b.
(a -> b -> Bool) -> These1 f g a -> These1 f g b -> Bool
liftEq a -> b -> Bool
eq (This1 f a
f)    (This1 f b
f')     = forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq f a
f f b
f'
    liftEq a -> b -> Bool
eq (That1 g a
g)    (That1 g b
g')     = forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq g a
g g b
g'
    liftEq a -> b -> Bool
eq (These1 f a
f g a
g) (These1 f b
f' g b
g') = forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq f a
f f b
f' Bool -> Bool -> Bool
&& forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq g a
g g b
g'

    liftEq a -> b -> Bool
_ This1  {} These1 f g b
_ = Bool
False
    liftEq a -> b -> Bool
_ That1  {} These1 f g b
_ = Bool
False
    liftEq a -> b -> Bool
_ These1 {} These1 f g b
_ = Bool
False
#else
    eq1 (This1 f)    (This1 f')     = eq1 f f'
    eq1 (That1 g)    (That1 g')     = eq1 g g'
    eq1 (These1 f g) (These1 f' g') = eq1 f f' && eq1 g g'

    eq1 This1  {} _ = False
    eq1 That1  {} _ = False
    eq1 These1 {} _ = False
#endif

-------------------------------------------------------------------------------
-- Ord1
-------------------------------------------------------------------------------

instance (Ord1 f, Ord1 g) => Ord1 (These1 f g) where
#ifdef LIFTED_FUNCTOR_CLASSES
    liftCompare :: forall a b.
(a -> b -> Ordering) -> These1 f g a -> These1 f g b -> Ordering
liftCompare  a -> b -> Ordering
cmp (This1 f a
f) (This1 f b
f') = forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp f a
f f b
f'
    liftCompare a -> b -> Ordering
_cmp (This1 f a
_) These1 f g b
_          = Ordering
LT
    liftCompare a -> b -> Ordering
_cmp These1 f g a
_         (This1 f b
_)  = Ordering
GT

    liftCompare  a -> b -> Ordering
cmp (That1 g a
g) (That1 g b
g') = forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp g a
g g b
g'
    liftCompare a -> b -> Ordering
_cmp (That1 g a
_) These1 f g b
_          = Ordering
LT
    liftCompare a -> b -> Ordering
_cmp These1 f g a
_         (That1 g b
_)  = Ordering
GT

    liftCompare  a -> b -> Ordering
cmp (These1 f a
f g a
g) (These1 f b
f' g b
g') =
        forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp f a
f f b
f' forall a. Monoid a => a -> a -> a
`mappend` forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp g a
g g b
g'
#else
    compare1 (This1 f) (This1 f') = compare1 f f'
    compare1 (This1 _) _          = LT
    compare1 _         (This1 _)  = GT

    compare1 (That1 g) (That1 g') = compare1 g g'
    compare1 (That1 _) _          = LT
    compare1 _         (That1 _)  = GT

    compare1  (These1 f g) (These1 f' g') =
        compare1 f f' `mappend` compare1 g g'
#endif


-------------------------------------------------------------------------------
-- Show1
-------------------------------------------------------------------------------

instance (Show1 f, Show1 g) => Show1 (These1 f g) where
#ifdef LIFTED_FUNCTOR_CLASSES
    liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> These1 f g a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (This1 f a
f) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"This1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
11 f a
f
    liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (That1 g a
g) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"That1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
11 g a
g
    liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (These1 f a
f g a
g) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"These1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
11 f a
f
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
11 g a
g
#else
    showsPrec1 d (This1 f) = showParen (d > 10)
        $ showString "This1 "
        . showsPrec1 11 f
    showsPrec1 d (That1 g) = showParen (d > 10)
        $ showString "That1 "
        . showsPrec1 11 g
    showsPrec1 d (These1 f g) = showParen (d > 10)
        $ showString "These1 "
        . showsPrec1 11 f
        . showChar ' '
        . showsPrec1 11 g
#endif

-------------------------------------------------------------------------------
-- Read1
-------------------------------------------------------------------------------

instance (Read1 f, Read1 g) => Read1 (These1 f g) where
#ifdef LIFTED_FUNCTOR_CLASSES
    liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (These1 f g a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl Int
d = forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ \String
s0 -> do
        (String
t, String
s1) <- ReadS String
lex String
s0
        case String
t of
            String
"This1" -> do
                (f a
x, String
s2) <- forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl Int
11 String
s1
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. f a -> These1 f g a
This1 f a
x, String
s2)
            String
"That1" -> do
                (g a
y, String
s2) <- forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl Int
11 String
s1
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. g a -> These1 f g a
That1 g a
y, String
s2)
            String
"These1" -> do
                (f a
x, String
s2) <- forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl Int
11 String
s1
                (g a
y, String
s3) <- forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl Int
11 String
s2
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. f a -> g a -> These1 f g a
These1 f a
x g a
y, String
s3)
            String
_ -> []
#else
    readsPrec1 d = readParen (d > 10) $ \s0 -> do
        (t, s1) <- lex s0
        case t of
            "This1" -> do
                (x, s2) <- readsPrec1 11 s1
                return (This1 x, s2)
            "That1" -> do
                (y, s2) <- readsPrec1 11 s1
                return (That1 y, s2)
            "These1" -> do
                (x, s2) <- readsPrec1 11 s1
                (y, s3) <- readsPrec1 11 s2
                return (These1 x y, s3)
            _ -> []
#endif

-------------------------------------------------------------------------------
-- Eq, Ord, Show, Read
-------------------------------------------------------------------------------

instance (Eq   (f a), Eq   (g a), Eq a)   => Eq (These1 f g a) where
    This1 f a
f    == :: These1 f g a -> These1 f g a -> Bool
== This1 f a
f'     = f a
f forall a. Eq a => a -> a -> Bool
== f a
f'
    That1 g a
g    == That1 g a
g'     = g a
g forall a. Eq a => a -> a -> Bool
== g a
g'
    These1 f a
f g a
g == These1 f a
f' g a
g' = f a
f forall a. Eq a => a -> a -> Bool
== f a
f' Bool -> Bool -> Bool
&& g a
g forall a. Eq a => a -> a -> Bool
== g a
g'

    This1  {} == These1 f g a
_ = Bool
False
    That1  {} == These1 f g a
_ = Bool
False
    These1 {} == These1 f g a
_ = Bool
False

instance (Ord  (f a), Ord  (g a), Ord a)  => Ord (These1 f g a) where
    compare :: These1 f g a -> These1 f g a -> Ordering
compare (This1 f a
f) (This1 f a
f') = forall a. Ord a => a -> a -> Ordering
compare f a
f f a
f'
    compare (This1 f a
_) These1 f g a
_          = Ordering
LT
    compare These1 f g a
_         (This1 f a
_)  = Ordering
GT

    compare (That1 g a
g) (That1 g a
g') = forall a. Ord a => a -> a -> Ordering
compare g a
g g a
g'
    compare (That1 g a
_) These1 f g a
_          = Ordering
LT
    compare These1 f g a
_         (That1 g a
_)  = Ordering
GT

    compare  (These1 f a
f g a
g) (These1 f a
f' g a
g') =
        forall a. Ord a => a -> a -> Ordering
compare f a
f f a
f' forall a. Monoid a => a -> a -> a
`mappend` forall a. Ord a => a -> a -> Ordering
compare g a
g g a
g'

instance (Show (f a), Show (g a), Show a) => Show (These1 f g a) where
    showsPrec :: Int -> These1 f g a -> ShowS
showsPrec Int
d (This1 f a
f) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"This1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 f a
f
    showsPrec Int
d (That1 g a
g) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"That1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 g a
g
    showsPrec Int
d (These1 f a
f g a
g) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
        forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"These1 "
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 f a
f
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 g a
g

instance (Read (f a), Read (g a), Read a) => Read (These1 f g a) where
    readsPrec :: Int -> ReadS (These1 f g a)
readsPrec Int
d = forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ \String
s0 -> do
        (String
t, String
s1) <- ReadS String
lex String
s0
        case String
t of
            String
"This1" -> do
                (f a
x, String
s2) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
s1
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. f a -> These1 f g a
This1 f a
x, String
s2)
            String
"That1" -> do
                (g a
y, String
s2) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
s1
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. g a -> These1 f g a
That1 g a
y, String
s2)
            String
"These1" -> do
                (f a
x, String
s2) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
s1
                (g a
y, String
s3) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
s2
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) (g :: * -> *) a. f a -> g a -> These1 f g a
These1 f a
x g a
y, String
s3)
            String
_ -> []

-------------------------------------------------------------------------------
-- deepseq
-------------------------------------------------------------------------------

#if MIN_VERSION_deepseq(1,4,3)
-- | This instance is available only with @deepseq >= 1.4.3.0@
instance (NFData1 f, NFData1 g) => NFData1 (These1 f g) where
    liftRnf :: forall a. (a -> ()) -> These1 f g a -> ()
liftRnf a -> ()
r (This1 f a
x)    = forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
r f a
x
    liftRnf a -> ()
r (That1 g a
y)    = forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
r g a
y
    liftRnf a -> ()
r (These1 f a
x g a
y) = forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
r f a
x seq :: forall a b. a -> b -> b
`seq` forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
r g a
y
#endif

-- | Available always
--
-- @since 1.2
instance (NFData (f a), NFData (g a), NFData a) => NFData (These1 f g a) where
    rnf :: These1 f g a -> ()
rnf (This1 f a
x)    = forall a. NFData a => a -> ()
rnf f a
x
    rnf (That1 g a
y)    = forall a. NFData a => a -> ()
rnf g a
y
    rnf (These1 f a
x g a
y) = forall a. NFData a => a -> ()
rnf f a
x seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf g a
y

-------------------------------------------------------------------------------
-- foldable1
-------------------------------------------------------------------------------

-- | @since 1.2
instance (F1.Foldable1 f, F1.Foldable1 g) => F1.Foldable1 (These1 f g) where
    foldMap1 :: forall m a. Semigroup m => (a -> m) -> These1 f g a -> m
foldMap1 a -> m
f (This1 f a
x)    = forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 a -> m
f f a
x
    foldMap1 a -> m
f (That1 g a
y)    = forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 a -> m
f g a
y
    foldMap1 a -> m
f (These1 f a
x g a
y) = forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 a -> m
f f a
x forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 a -> m
f g a
y

    foldrMap1 :: forall a b. (a -> b) -> (a -> b -> b) -> These1 f g a -> b
foldrMap1 a -> b
f a -> b -> b
g (This1 f a
x)    = forall (t :: * -> *) a b.
Foldable1 t =>
(a -> b) -> (a -> b -> b) -> t a -> b
F1.foldrMap1 a -> b
f a -> b -> b
g f a
x
    foldrMap1 a -> b
f a -> b -> b
g (That1 g a
y)    = forall (t :: * -> *) a b.
Foldable1 t =>
(a -> b) -> (a -> b -> b) -> t a -> b
F1.foldrMap1 a -> b
f a -> b -> b
g g a
y
    foldrMap1 a -> b
f a -> b -> b
g (These1 f a
x g a
y) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> b -> b
g (forall (t :: * -> *) a b.
Foldable1 t =>
(a -> b) -> (a -> b -> b) -> t a -> b
F1.foldrMap1 a -> b
f a -> b -> b
g g a
y) f a
x

    head :: forall a. These1 f g a -> a
head (This1 f a
x)    = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.head f a
x
    head (That1 g a
y)    = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.head g a
y
    head (These1 f a
x g a
_) = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.head f a
x

    last :: forall a. These1 f g a -> a
last (This1 f a
x)    = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.last f a
x
    last (That1 g a
y)    = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.last g a
y
    last (These1 f a
_ g a
y) = forall (t :: * -> *) a. Foldable1 t => t a -> a
F1.last g a
y