{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE DeriveGeneric #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE Safe #-}{-# LANGUAGE StandaloneDeriving #-}------------------------------------------------------------------------------- |-- Module : Data.Functor.Product-- Copyright : (c) Ross Paterson 2010-- License : BSD-style (see the file LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- Products, lifted to functors.---- @since 4.9.0.0-----------------------------------------------------------------------------moduleData.Functor.Product (Product (..),)whereimportControl.Applicative importGHC.Internal.Control.Monad (MonadPlus (..))importGHC.Internal.Control.Monad.Fix (MonadFix (..))importControl.Monad.Zip (MonadZip (mzipWith ))importGHC.Internal.Data.Data (Data )importData.Functor.Classes importGHC.Generics (Generic ,Generic1 )importPrelude -- $setup-- >>> import Prelude-- | Lifted product of functors.---- ==== __Examples__---- >>> fmap (+1) (Pair [1, 2, 3] (Just 0))-- Pair [2,3,4] (Just 1)---- >>> Pair "Hello, " (Left 'x') <> Pair "World" (Right 'y')-- Pair "Hello, World" (Right 'y')dataProduct f g a =Pair (f a )(g a )deriving(Typeable (Product f g a) Typeable (Product f g a) => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product f g a -> c (Product f g a)) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a)) -> (Product f g a -> Constr) -> (Product f g a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a))) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a))) -> ((forall b. Data b => b -> b) -> Product f g a -> Product f g a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r) -> (forall u. (forall d. Data d => d -> u) -> Product f g a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> Product f g a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a)) -> Data (Product f g a) Product f g a -> Constr Product f g a -> DataType (forall b. Data b => b -> b) -> Product f g a -> Product f g a 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 u. Int -> (forall d. Data d => d -> u) -> Product f g a -> u forall u. (forall d. Data d => d -> u) -> Product f g a -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Typeable (Product f g a) forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Product f g a -> Constr forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Product f g a -> DataType forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall b. Data b => b -> b) -> Product f g a -> Product f g a forall k (f :: k -> *) (g :: k -> *) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Int -> (forall d. Data d => d -> u) -> Product f g a -> u forall k (f :: k -> *) (g :: k -> *) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall d. Data d => d -> u) -> Product f g a -> [u] forall k (f :: k -> *) (g :: k -> *) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r forall k (f :: k -> *) (g :: k -> *) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r forall k (f :: k -> *) (g :: k -> *) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Monad m) => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) forall k (f :: k -> *) (g :: k -> *) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), MonadPlus m) => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) forall k (f :: k -> *) (g :: k -> *) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) forall k (f :: k -> *) (g :: k -> *) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product f g a -> c (Product f g a) forall k (f :: k -> *) (g :: k -> *) (a :: k) (t :: * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) forall k (f :: k -> *) (g :: k -> *) (a :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product f g a -> c (Product f g a) forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) $cgfoldl :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product f g a -> c (Product f g a) gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product f g a -> c (Product f g a) $cgunfold :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) $ctoConstr :: forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Product f g a -> Constr toConstr :: Product f g a -> Constr $cdataTypeOf :: forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Product f g a -> DataType dataTypeOf :: Product f g a -> DataType $cdataCast1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (t :: * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) $cdataCast2 :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) $cgmapT :: forall k (f :: k -> *) (g :: k -> *) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall b. Data b => b -> b) -> Product f g a -> Product f g a gmapT :: (forall b. Data b => b -> b) -> Product f g a -> Product f g a $cgmapQl :: forall k (f :: k -> *) (g :: k -> *) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r $cgmapQr :: forall k (f :: k -> *) (g :: k -> *) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r $cgmapQ :: forall k (f :: k -> *) (g :: k -> *) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (forall d. Data d => d -> u) -> Product f g a -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> Product f g a -> [u] $cgmapQi :: forall k (f :: k -> *) (g :: k -> *) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Int -> (forall d. Data d => d -> u) -> Product f g a -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Product f g a -> u $cgmapM :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), Monad m) => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) $cgmapMp :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), MonadPlus m) => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) $cgmapMo :: forall k (f :: k -> *) (g :: k -> *) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a), MonadPlus m) => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) Data -- ^ @since 4.9.0.0,(forall x. Product f g a -> Rep (Product f g a) x) -> (forall x. Rep (Product f g a) x -> Product f g a) -> Generic (Product f g a) forall x. Rep (Product f g a) x -> Product f g a forall x. Product f g a -> Rep (Product f g a) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Rep (Product f g a) x -> Product f g a forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Product f g a -> Rep (Product f g a) x $cfrom :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Product f g a -> Rep (Product f g a) x from :: forall x. Product f g a -> Rep (Product f g a) x $cto :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Rep (Product f g a) x -> Product f g a to :: forall x. Rep (Product f g a) x -> Product f g a Generic -- ^ @since 4.9.0.0,(forall (a :: k). Product f g a -> Rep1 (Product f g) a) -> (forall (a :: k). Rep1 (Product f g) a -> Product f g a) -> Generic1 (Product f g) forall (a :: k). Rep1 (Product f g) a -> Product f g a forall (a :: k). Product f g a -> Rep1 (Product f g) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f forall k (f :: k -> *) (g :: k -> *) (a :: k). Rep1 (Product f g) a -> Product f g a forall k (f :: k -> *) (g :: k -> *) (a :: k). Product f g a -> Rep1 (Product f g) a $cfrom1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). Product f g a -> Rep1 (Product f g) a from1 :: forall (a :: k). Product f g a -> Rep1 (Product f g) a $cto1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). Rep1 (Product f g) a -> Product f g a to1 :: forall (a :: k). Rep1 (Product f g) a -> Product f g a Generic1 -- ^ @since 4.9.0.0)-- | @since 4.18.0.0derivinginstance(Eq (f a ),Eq (g a ))=>Eq (Product f g a )-- | @since 4.18.0.0derivinginstance(Ord (f a ),Ord (g a ))=>Ord (Product f g a )-- | @since 4.18.0.0derivinginstance(Read (f a ),Read (g a ))=>Read (Product f g a )-- | @since 4.18.0.0derivinginstance(Show (f a ),Show (g a ))=>Show (Product f g a )-- | @since 4.9.0.0instance(Eq1 f ,Eq1 g )=>Eq1 (Product f g )whereliftEq :: forall a b. (a -> b -> Bool) -> Product f g a -> Product f g b -> Bool liftEq a -> b -> Bool eq (Pair f a x1 g a y1 )(Pair f b x2 g b y2 )=(a -> b -> Bool) -> f a -> f b -> Bool forall a b. (a -> b -> Bool) -> f a -> f b -> Bool forall (f :: * -> *) a b. Eq1 f => (a -> b -> Bool) -> f a -> f b -> Bool liftEq a -> b -> Bool eq f a x1 f b x2 Bool -> Bool -> Bool && (a -> b -> Bool) -> g a -> g b -> Bool forall a b. (a -> b -> Bool) -> g a -> g b -> Bool forall (f :: * -> *) a b. Eq1 f => (a -> b -> Bool) -> f a -> f b -> Bool liftEq a -> b -> Bool eq g a y1 g b y2 -- | @since 4.9.0.0instance(Ord1 f ,Ord1 g )=>Ord1 (Product f g )whereliftCompare :: forall a b. (a -> b -> Ordering) -> Product f g a -> Product f g b -> Ordering liftCompare a -> b -> Ordering comp (Pair f a x1 g a y1 )(Pair f b x2 g b y2 )=(a -> b -> Ordering) -> f a -> f b -> Ordering forall a b. (a -> b -> Ordering) -> f a -> f b -> Ordering forall (f :: * -> *) a b. Ord1 f => (a -> b -> Ordering) -> f a -> f b -> Ordering liftCompare a -> b -> Ordering comp f a x1 f b x2 Ordering -> Ordering -> Ordering forall a. Monoid a => a -> a -> a `mappend` (a -> b -> Ordering) -> g a -> g b -> Ordering forall a b. (a -> b -> Ordering) -> g a -> g b -> Ordering forall (f :: * -> *) a b. Ord1 f => (a -> b -> Ordering) -> f a -> f b -> Ordering liftCompare a -> b -> Ordering comp g a y1 g b y2 -- | @since 4.9.0.0instance(Read1 f ,Read1 g )=>Read1 (Product f g )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) liftReadPrec ReadPrec a rp ReadPrec [a] rl =ReadPrec (Product f g a) -> ReadPrec (Product f g a) forall a. ReadPrec a -> ReadPrec a readData (ReadPrec (Product f g a) -> ReadPrec (Product f g a)) -> ReadPrec (Product f g a) -> ReadPrec (Product f g a) forall a b. (a -> b) -> a -> b $ ReadPrec (f a) -> ReadPrec (g a) -> String -> (f a -> g a -> Product f g a) -> ReadPrec (Product f g a) forall a b t. ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t readBinaryWith (ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) forall (f :: * -> *) a. Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) liftReadPrec ReadPrec a rp ReadPrec [a] rl )(ReadPrec a -> ReadPrec [a] -> ReadPrec (g a) forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (g a) forall (f :: * -> *) a. Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) liftReadPrec ReadPrec a rp ReadPrec [a] rl )String "Pair"f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] forall (f :: * -> *) a. Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] forall (f :: * -> *) a. Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] liftReadListDefault -- | @since 4.9.0.0instance(Show1 f ,Show1 g )=>Show1 (Product f g )whereliftShowsPrec :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl Int d (Pair f a x g a y )=(Int -> f a -> ShowS) -> (Int -> g a -> ShowS) -> String -> Int -> f a -> g a -> ShowS forall a b. (Int -> a -> ShowS) -> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS showsBinaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS forall (f :: * -> *) a. Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl )((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> g a -> ShowS forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> g a -> ShowS forall (f :: * -> *) a. Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl )String "Pair"Int d f a x g a y -- | @since 4.9.0.0instance(Functor f ,Functor g )=>Functor (Product f g )wherefmap :: forall a b. (a -> b) -> Product f g a -> Product f g b fmap a -> b f (Pair f a x g a y )=f b -> g b -> Product f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair ((a -> b) -> f a -> f b forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> b f f a x )((a -> b) -> g a -> g b forall a b. (a -> b) -> g a -> g b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> b f g a y )a a <$ :: forall a b. a -> Product f g b -> Product f g a <$ (Pair f b x g b y )=f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (a a a -> f b -> f a forall a b. a -> f b -> f a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ f b x )(a a a -> g b -> g a forall a b. a -> g b -> g a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ g b y )-- | @since 4.9.0.0instance(Foldable f ,Foldable g )=>Foldable (Product f g )wherefoldMap :: forall m a. Monoid m => (a -> m) -> Product f g a -> m foldMap a -> m f (Pair f a x g a y )=(a -> m) -> f a -> m forall m a. Monoid m => (a -> m) -> f a -> m forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap a -> m f f a x m -> m -> m forall a. Monoid a => a -> a -> a `mappend` (a -> m) -> g a -> m forall m a. Monoid m => (a -> m) -> g a -> m forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap a -> m f g a y -- | @since 4.9.0.0instance(Traversable f ,Traversable g )=>Traversable (Product f g )wheretraverse :: forall (f :: * -> *) a b. Applicative f => (a -> f b) -> Product f g a -> f (Product f g b) traverse a -> f b f (Pair f a x g a y )=(f b -> g b -> Product f g b) -> f (f b) -> f (g b) -> f (Product f g b) forall a b c. (a -> b -> c) -> f a -> f b -> f c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 f b -> g b -> Product f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair ((a -> f b) -> f a -> f (f b) forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) forall (f :: * -> *) a b. Applicative f => (a -> f b) -> f a -> f (f b) traverse a -> f b f f a x )((a -> f b) -> g a -> f (g b) forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) forall (f :: * -> *) a b. Applicative f => (a -> f b) -> g a -> f (g b) traverse a -> f b f g a y )-- | @since 4.9.0.0instance(Applicative f ,Applicative g )=>Applicative (Product f g )wherepure :: forall a. a -> Product f g a pure a x =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (a -> f a forall a. a -> f a forall (f :: * -> *) a. Applicative f => a -> f a pure a x )(a -> g a forall a. a -> g a forall (f :: * -> *) a. Applicative f => a -> f a pure a x )Pair f (a -> b) f g (a -> b) g <*> :: forall a b. Product f g (a -> b) -> Product f g a -> Product f g b <*> Pair f a x g a y =f b -> g b -> Product f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (f (a -> b) f f (a -> b) -> f a -> f b forall a b. f (a -> b) -> f a -> f b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> f a x )(g (a -> b) g g (a -> b) -> g a -> g b forall a b. g (a -> b) -> g a -> g b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> g a y )liftA2 :: forall a b c. (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c liftA2 a -> b -> c f (Pair f a a g a b )(Pair f b x g b y )=f c -> g c -> Product f g c forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair ((a -> b -> c) -> f a -> f b -> f c forall a b c. (a -> b -> c) -> f a -> f b -> f c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 a -> b -> c f f a a f b x )((a -> b -> c) -> g a -> g b -> g c forall a b c. (a -> b -> c) -> g a -> g b -> g c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 a -> b -> c f g a b g b y )-- | @since 4.9.0.0instance(Alternative f ,Alternative g )=>Alternative (Product f g )whereempty :: forall a. Product f g a empty =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair f a forall a. f a forall (f :: * -> *) a. Alternative f => f a empty g a forall a. g a forall (f :: * -> *) a. Alternative f => f a empty Pair f a x1 g a y1 <|> :: forall a. Product f g a -> Product f g a -> Product f g a <|> Pair f a x2 g a y2 =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (f a x1 f a -> f a -> f a forall a. f a -> f a -> f a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> f a x2 )(g a y1 g a -> g a -> g a forall a. g a -> g a -> g a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> g a y2 )-- | @since 4.9.0.0instance(Monad f ,Monad g )=>Monad (Product f g )wherePair f a m g a n >>= :: forall a b. Product f g a -> (a -> Product f g b) -> Product f g b >>= a -> Product f g b f =f b -> g b -> Product f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (f a m f a -> (a -> f b) -> f b forall a b. f a -> (a -> f b) -> f b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Product f g b -> f b forall {k} {f :: k -> *} {g :: k -> *} {a :: k}. Product f g a -> f a fstP (Product f g b -> f b) -> (a -> Product f g b) -> a -> f b forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Product f g b f )(g a n g a -> (a -> g b) -> g b forall a b. g a -> (a -> g b) -> g b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Product f g b -> g b forall {k} {f :: k -> *} {g :: k -> *} {a :: k}. Product f g a -> g a sndP (Product f g b -> g b) -> (a -> Product f g b) -> a -> g b forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Product f g b f )wherefstP :: Product f g a -> f a fstP (Pair f a a g a _)=f a a sndP :: Product f g a -> g a sndP (Pair f a _g a b )=g a b -- | @since 4.9.0.0instance(MonadPlus f ,MonadPlus g )=>MonadPlus (Product f g )wheremzero :: forall a. Product f g a mzero =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair f a forall a. f a forall (m :: * -> *) a. MonadPlus m => m a mzero g a forall a. g a forall (m :: * -> *) a. MonadPlus m => m a mzero Pair f a x1 g a y1 mplus :: forall a. Product f g a -> Product f g a -> Product f g a `mplus` Pair f a x2 g a y2 =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (f a x1 f a -> f a -> f a forall a. f a -> f a -> f a forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a `mplus` f a x2 )(g a y1 g a -> g a -> g a forall a. g a -> g a -> g a forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a `mplus` g a y2 )-- | @since 4.9.0.0instance(MonadFix f ,MonadFix g )=>MonadFix (Product f g )wheremfix :: forall a. (a -> Product f g a) -> Product f g a mfix a -> Product f g a f =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair ((a -> f a) -> f a forall a. (a -> f a) -> f a forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a mfix (Product f g a -> f a forall {k} {f :: k -> *} {g :: k -> *} {a :: k}. Product f g a -> f a fstP (Product f g a -> f a) -> (a -> Product f g a) -> a -> f a forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Product f g a f ))((a -> g a) -> g a forall a. (a -> g a) -> g a forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a mfix (Product f g a -> g a forall {k} {f :: k -> *} {g :: k -> *} {a :: k}. Product f g a -> g a sndP (Product f g a -> g a) -> (a -> Product f g a) -> a -> g a forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Product f g a f ))wherefstP :: Product f g a -> f a fstP (Pair f a a g a _)=f a a sndP :: Product f g a -> g a sndP (Pair f a _g a b )=g a b -- | @since 4.9.0.0instance(MonadZip f ,MonadZip g )=>MonadZip (Product f g )wheremzipWith :: forall a b c. (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c mzipWith a -> b -> c f (Pair f a x1 g a y1 )(Pair f b x2 g b y2 )=f c -> g c -> Product f g c forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair ((a -> b -> c) -> f a -> f b -> f c forall a b c. (a -> b -> c) -> f a -> f b -> f c forall (m :: * -> *) a b c. MonadZip m => (a -> b -> c) -> m a -> m b -> m c mzipWith a -> b -> c f f a x1 f b x2 )((a -> b -> c) -> g a -> g b -> g c forall a b c. (a -> b -> c) -> g a -> g b -> g c forall (m :: * -> *) a b c. MonadZip m => (a -> b -> c) -> m a -> m b -> m c mzipWith a -> b -> c f g a y1 g b y2 )-- | @since 4.16.0.0instance(Semigroup (f a ),Semigroup (g a ))=>Semigroup (Product f g a )wherePair f a x1 g a y1 <> :: Product f g a -> Product f g a -> Product f g a <> Pair f a x2 g a y2 =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair (f a x1 f a -> f a -> f a forall a. Semigroup a => a -> a -> a <> f a x2 )(g a y1 g a -> g a -> g a forall a. Semigroup a => a -> a -> a <> g a y2 )-- | @since 4.16.0.0instance(Monoid (f a ),Monoid (g a ))=>Monoid (Product f g a )wheremempty :: Product f g a mempty =f a -> g a -> Product f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> g a -> Product f g a Pair f a forall a. Monoid a => a mempty g a forall a. Monoid a => a mempty