(original) (raw)
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE Safe #-}
module Data.Functor.Product ( Product(..), ) where
import Control.Applicative import Control.Monad (MonadPlus(..)) import Control.Monad.Fix (MonadFix(..)) import Control.Monad.Zip (MonadZip(mzipWith)) import Data.Data (Data) import Data.Functor.Classes import GHC.Generics (Generic, Generic1) import Text.Read (Read(..), readListDefault, readListPrecDefault)
data Product 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))
gmapMo :: 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)
gmapMp :: forall (m :: * -> *).
MonadPlus 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)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Product f g a -> m (Product f g a)
$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)
gmapQi :: forall u. Int -> (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
gmapQ :: forall u. (forall d. Data d => d -> u) -> Product f g a -> [u]
$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]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Product f g a -> r
$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
gmapT :: (forall b. Data b => b -> b) -> Product f g a -> 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
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Product f g a))
$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))
dataTypeOf :: Product f g a -> DataType
$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
toConstr :: Product f g a -> Constr
$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
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
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)
$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)
Data
, (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
$cto :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x.
Rep (Product f g a) x -> Product f g a
$cfrom :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x.
Product f g a -> Rep (Product f g a) x
Generic
, (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
$cto1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k).
Rep1 (Product f g) a -> Product f g a
$cfrom1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k).
Product f g a -> Rep1 (Product f g) a
Generic1
)
instance (Eq1 f, Eq1 g) => Eq1 (Product f g) where liftEq :: 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 (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 (f :: * -> *) a b. Eq1 f => (a -> b -> Bool) -> f a -> f b -> Bool liftEq a -> b -> Bool eq g a y1 g b y2
instance (Ord1 f, Ord1 g) => Ord1 (Product f g) where
liftCompare :: 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 (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 (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
comp g a
y1 g b
y2
instance (Read1 f, Read1 g) => Read1 (Product f g) where liftReadPrec :: 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 (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 (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
instance (Show1 f, Show1 g) => Show1 (Product f g) where liftShowsPrec :: 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 (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 (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
instance (Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) where == :: Product f g a -> Product f g a -> Bool (==) = Product f g a -> Product f g a -> Bool forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool eq1
instance (Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) where compare :: Product f g a -> Product f g a -> Ordering compare = Product f g a -> Product f g a -> Ordering forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering compare1
instance (Read1 f, Read1 g, Read a) => Read (Product f g a) where readPrec :: ReadPrec (Product f g a) readPrec = ReadPrec (Product f g a) forall (f :: * -> *) a. (Read1 f, Read a) => ReadPrec (f a) readPrec1
readListPrec :: ReadPrec [Product f g a]readListPrec = ReadPrec [Product f g a] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Product f g a] readList = ReadS [Product f g a] forall a. Read a => ReadS [a] readListDefault
instance (Show1 f, Show1 g, Show a) => Show (Product f g a) where showsPrec :: Int -> Product f g a -> ShowS showsPrec = Int -> Product f g a -> ShowS forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS showsPrec1
instance (Functor f, Functor g) => Functor (Product f g) where fmap :: 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 (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 (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 (f :: * -> *) a b. Functor f => a -> f b -> f a <$ f b x) (a a a -> g b -> g a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ g b y)
instance (Foldable f, Foldable g) => Foldable (Product f g) where
foldMap :: 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 (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 (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f g a
y
instance (Traversable f, Traversable g) => Traversable (Product f g) where traverse :: 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 (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) 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) traverse a -> f b f g a y)
instance (Applicative f, Applicative g) => Applicative (Product f g) where pure :: 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 (f :: * -> *) a. Applicative f => a -> f a pure a x) (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 (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 (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 (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 (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)
instance (Alternative f, Alternative g) => Alternative (Product f g) where empty :: 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 (f :: * -> *) a. Alternative f => f a empty 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 (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> f a x2) (g a y1 g a -> g a -> g a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> g a y2)
instance (Monad f, Monad g) => Monad (Product f g) where Pair 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 (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 (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) where fstP :: 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
instance (MonadPlus f, MonadPlus g) => MonadPlus (Product f g) where
mzero :: 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 (m :: * -> *) a. MonadPlus m => m a
mzero 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 (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus f a
x2) (g a
y1 g a -> g a -> g a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus g a
y2)
instance (MonadFix f, MonadFix g) => MonadFix (Product f g) where mfix :: 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 (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 (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)) where fstP :: 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
instance (MonadZip f, MonadZip g) => MonadZip (Product f g) where mzipWith :: 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 (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 (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)
instance (Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) where Pair 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)
instance (Monoid (f a), Monoid (g a)) => Monoid (Product f g a) where mempty :: 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