{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE DeriveGeneric #-}{-# LANGUAGE GADTs #-}{-# LANGUAGE GeneralizedNewtypeDeriving #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE StandaloneDeriving #-}------------------------------------------------------------------------------- |-- Module : Data.Functor.Compose-- Copyright : (c) Ross Paterson 2010-- License : BSD-style (see the file LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- Composition of functors.---- @since 4.9.0.0-----------------------------------------------------------------------------moduleData.Functor.Compose(Compose (..),)whereimportData.Functor.Classes importControl.Applicative importData.Coerce (coerce )importData.Data (Data )importData.Type.Equality (TestEquality (..),(:~:) (..))importGHC.Generics (Generic ,Generic1 )importText.Read (Read (..),ReadPrec ,readListDefault ,readListPrecDefault )infixr9`Compose` -- | Right-to-left composition of functors.-- The composition of applicative functors is always applicative,-- but the composition of monads is not always a monad.newtypeCompose f g a =Compose {forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). Compose f g a -> f (g a) getCompose ::f (g a )}deriving(Typeable (Compose f g a) Typeable (Compose f g a) => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compose f g a -> c (Compose f g a)) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a)) -> (Compose f g a -> Constr) -> (Compose f g a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a))) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a))) -> ((forall b. Data b => b -> b) -> Compose f g a -> Compose f g a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r) -> (forall u. (forall d. Data d => d -> u) -> Compose f g a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> Compose f g a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a)) -> Data (Compose f g a) Compose f g a -> Constr Compose f g a -> DataType (forall b. Data b => b -> b) -> Compose f g a -> Compose 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) -> Compose f g a -> u forall u. (forall d. Data d => d -> u) -> Compose f g a -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Typeable (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Compose f g a -> Constr forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Compose f g a -> DataType forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall b. Data b => b -> b) -> Compose f g a -> Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Int -> (forall d. Data d => d -> u) -> Compose f g a -> u forall k (f :: k -> *) k (g :: k -> k) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall d. Data d => d -> u) -> Compose f g a -> [u] forall k (f :: k -> *) k (g :: k -> k) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r forall k (f :: k -> *) k (g :: k -> k) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r forall k (f :: k -> *) k (g :: k -> k) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Monad m) => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), MonadPlus m) => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compose f g a -> c (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k) (t :: * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) forall k (f :: k -> *) k (g :: k -> k) (a :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compose f g a -> c (Compose f g a) forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) $cgfoldl :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compose f g a -> c (Compose f g a) gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compose f g a -> c (Compose f g a) $cgunfold :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) $ctoConstr :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Compose f g a -> Constr toConstr :: Compose f g a -> Constr $cdataTypeOf :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Compose f g a -> DataType dataTypeOf :: Compose f g a -> DataType $cdataCast1 :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (t :: * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) $cdataCast2 :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) $cgmapT :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall b. Data b => b -> b) -> Compose f g a -> Compose f g a gmapT :: (forall b. Data b => b -> b) -> Compose f g a -> Compose f g a $cgmapQl :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r $cgmapQr :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) r r'. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r $cgmapQ :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => (forall d. Data d => d -> u) -> Compose f g a -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> Compose f g a -> [u] $cgmapQi :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) u. (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a))) => Int -> (forall d. Data d => d -> u) -> Compose f g a -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Compose f g a -> u $cgmapM :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), Monad m) => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) $cgmapMp :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), MonadPlus m) => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) $cgmapMo :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) (m :: * -> *). (Typeable a, Typeable f, Typeable g, Typeable k, Typeable k, Data (f (g a)), MonadPlus m) => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) Data -- ^ @since 4.9.0.0,(forall x. Compose f g a -> Rep (Compose f g a) x) -> (forall x. Rep (Compose f g a) x -> Compose f g a) -> Generic (Compose f g a) forall x. Rep (Compose f g a) x -> Compose f g a forall x. Compose f g a -> Rep (Compose f g a) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> *) k (g :: k -> k) (a :: k) x. Rep (Compose f g a) x -> Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k) x. Compose f g a -> Rep (Compose f g a) x $cfrom :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) x. Compose f g a -> Rep (Compose f g a) x from :: forall x. Compose f g a -> Rep (Compose f g a) x $cto :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) x. Rep (Compose f g a) x -> Compose f g a to :: forall x. Rep (Compose f g a) x -> Compose f g a Generic -- ^ @since 4.9.0.0,(forall (a :: k). Compose f g a -> Rep1 (Compose f g) a) -> (forall (a :: k). Rep1 (Compose f g) a -> Compose f g a) -> Generic1 (Compose f g) forall (a :: k). Rep1 (Compose f g) a -> Compose f g a forall (a :: k). Compose f g a -> Rep1 (Compose 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 (f :: * -> *) k (g :: k -> *) (a :: k). Functor f => Rep1 (Compose f g) a -> Compose f g a forall (f :: * -> *) k (g :: k -> *) (a :: k). Functor f => Compose f g a -> Rep1 (Compose f g) a $cfrom1 :: forall (f :: * -> *) k (g :: k -> *) (a :: k). Functor f => Compose f g a -> Rep1 (Compose f g) a from1 :: forall (a :: k). Compose f g a -> Rep1 (Compose f g) a $cto1 :: forall (f :: * -> *) k (g :: k -> *) (a :: k). Functor f => Rep1 (Compose f g) a -> Compose f g a to1 :: forall (a :: k). Rep1 (Compose f g) a -> Compose f g a Generic1 -- ^ @since 4.9.0.0,NonEmpty (Compose f g a) -> Compose f g a Compose f g a -> Compose f g a -> Compose f g a (Compose f g a -> Compose f g a -> Compose f g a) -> (NonEmpty (Compose f g a) -> Compose f g a) -> (forall b. Integral b => b -> Compose f g a -> Compose f g a) -> Semigroup (Compose f g a) forall b. Integral b => b -> Compose f g a -> Compose f g a forall a. (a -> a -> a) -> (NonEmpty a -> a) -> (forall b. Integral b => b -> a -> a) -> Semigroup a forall k (f :: k -> *) k (g :: k -> k) (a :: k). Semigroup (f (g a)) => NonEmpty (Compose f g a) -> Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k). Semigroup (f (g a)) => Compose f g a -> Compose f g a -> Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k) b. (Semigroup (f (g a)), Integral b) => b -> Compose f g a -> Compose f g a $c<> :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). Semigroup (f (g a)) => Compose f g a -> Compose f g a -> Compose f g a <> :: Compose f g a -> Compose f g a -> Compose f g a $csconcat :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). Semigroup (f (g a)) => NonEmpty (Compose f g a) -> Compose f g a sconcat :: NonEmpty (Compose f g a) -> Compose f g a $cstimes :: forall k (f :: k -> *) k (g :: k -> k) (a :: k) b. (Semigroup (f (g a)), Integral b) => b -> Compose f g a -> Compose f g a stimes :: forall b. Integral b => b -> Compose f g a -> Compose f g a Semigroup -- ^ @since 4.16.0.0,Semigroup (Compose f g a) Compose f g a Semigroup (Compose f g a) => Compose f g a -> (Compose f g a -> Compose f g a -> Compose f g a) -> ([Compose f g a] -> Compose f g a) -> Monoid (Compose f g a) [Compose f g a] -> Compose f g a Compose f g a -> Compose f g a -> Compose f g a forall a. Semigroup a => a -> (a -> a -> a) -> ([a] -> a) -> Monoid a forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => Semigroup (Compose f g a) forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => [Compose f g a] -> Compose f g a forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => Compose f g a -> Compose f g a -> Compose f g a $cmempty :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => Compose f g a mempty :: Compose f g a $cmappend :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => Compose f g a -> Compose f g a -> Compose f g a mappend :: Compose f g a -> Compose f g a -> Compose f g a $cmconcat :: forall k (f :: k -> *) k (g :: k -> k) (a :: k). Monoid (f (g a)) => [Compose f g a] -> Compose f g a mconcat :: [Compose f g a] -> Compose f g a Monoid -- ^ @since 4.16.0.0)-- Instances of Prelude classes-- | @since 4.18.0.0derivinginstanceEq (f (g a ))=>Eq (Compose f g a )-- | @since 4.18.0.0derivinginstanceOrd (f (g a ))=>Ord (Compose f g a )-- | @since 4.18.0.0instanceRead (f (g a ))=>Read (Compose f g a )wherereadPrec :: ReadPrec (Compose f g a) readPrec =ReadPrec (f (g a)) -> ReadPrec (Compose f g a) forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). ReadPrec (f (g a)) -> ReadPrec (Compose f g a) liftReadPrecCompose ReadPrec (f (g a)) forall a. Read a => ReadPrec a readPrec readListPrec :: ReadPrec [Compose f g a] readListPrec =ReadPrec [Compose f g a] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Compose f g a] readList =ReadS [Compose f g a] forall a. Read a => ReadS [a] readListDefault -- | @since 4.18.0.0instanceShow (f (g a ))=>Show (Compose f g a )whereshowsPrec :: Int -> Compose f g a -> ShowS showsPrec =(Int -> f (g a) -> ShowS) -> Int -> Compose f g a -> ShowS forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). (Int -> f (g a) -> ShowS) -> Int -> Compose f g a -> ShowS liftShowsPrecCompose Int -> f (g a) -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec -- Instances of lifted Prelude classes-- | @since 4.9.0.0instance(Eq1 f ,Eq1 g )=>Eq1 (Compose f g )whereliftEq :: forall a b. (a -> b -> Bool) -> Compose f g a -> Compose f g b -> Bool liftEq a -> b -> Bool eq (Compose f (g a) x )(Compose f (g b) y )=(g a -> g b -> Bool) -> f (g a) -> f (g 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) -> 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 )f (g a) x f (g b) y -- | @since 4.9.0.0instance(Ord1 f ,Ord1 g )=>Ord1 (Compose f g )whereliftCompare :: forall a b. (a -> b -> Ordering) -> Compose f g a -> Compose f g b -> Ordering liftCompare a -> b -> Ordering comp (Compose f (g a) x )(Compose f (g b) y )=(g a -> g b -> Ordering) -> f (g a) -> f (g 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) -> 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 )f (g a) x f (g b) y -- | @since 4.9.0.0instance(Read1 f ,Read1 g )=>Read1 (Compose f g )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) liftReadPrec ReadPrec a rp ReadPrec [a] rl =ReadPrec (f (g a)) -> ReadPrec (Compose f g a) forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). ReadPrec (f (g a)) -> ReadPrec (Compose f g a) liftReadPrecCompose (ReadPrec (g a) -> ReadPrec [g a] -> ReadPrec (f (g a)) forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) forall (f :: * -> *) a. Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) liftReadPrec ReadPrec (g a) rp' ReadPrec [g a] rl' )whererp' :: ReadPrec (g a) rp' =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 rl' :: ReadPrec [g 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] liftReadListPrec ReadPrec a rp ReadPrec [a] rl liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose 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 [Compose f g a] liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Compose 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 (Compose f g )whereliftShowsPrec :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose f g a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl =(Int -> f (g a) -> ShowS) -> Int -> Compose f g a -> ShowS forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). (Int -> f (g a) -> ShowS) -> Int -> Compose f g a -> ShowS liftShowsPrecCompose ((Int -> g a -> ShowS) -> ([g a] -> ShowS) -> Int -> f (g 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 -> g a -> ShowS sp' [g a] -> ShowS sl' )wheresp' :: Int -> g a -> ShowS sp' =(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 sl' :: [g a] -> ShowS sl' =(Int -> a -> ShowS) -> ([a] -> ShowS) -> [g a] -> ShowS forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> [g a] -> ShowS forall (f :: * -> *) a. Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS liftShowList Int -> a -> ShowS sp [a] -> ShowS sl -- The workhorse for Compose's Read and Read1 instances.liftReadPrecCompose ::ReadPrec (f (g a ))->ReadPrec (Compose f g a )liftReadPrecCompose :: forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). ReadPrec (f (g a)) -> ReadPrec (Compose f g a) liftReadPrecCompose ReadPrec (f (g a)) rp =ReadPrec (Compose f g a) -> ReadPrec (Compose f g a) forall a. ReadPrec a -> ReadPrec a readData (ReadPrec (Compose f g a) -> ReadPrec (Compose f g a)) -> ReadPrec (Compose f g a) -> ReadPrec (Compose f g a) forall a b. (a -> b) -> a -> b $ ReadPrec (f (g a)) -> String -> (f (g a) -> Compose f g a) -> ReadPrec (Compose f g a) forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t readUnaryWith ReadPrec (f (g a)) rp String "Compose"f (g a) -> Compose f g a forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose -- The workhorse for Compose's Show and Show1 instances.liftShowsPrecCompose ::(Int ->f (g a )->ShowS )->Int ->Compose f g a ->ShowS liftShowsPrecCompose :: forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). (Int -> f (g a) -> ShowS) -> Int -> Compose f g a -> ShowS liftShowsPrecCompose Int -> f (g a) -> ShowS sp Int d (Compose f (g a) x )=(Int -> f (g a) -> ShowS) -> String -> Int -> f (g a) -> ShowS forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS showsUnaryWith Int -> f (g a) -> ShowS sp String "Compose"Int d f (g a) x -- Functor instances-- | @since 4.9.0.0instance(Functor f ,Functor g )=>Functor (Compose f g )wherefmap :: forall a b. (a -> b) -> Compose f g a -> Compose f g b fmap a -> b f (Compose f (g a) x )=f (g b) -> Compose f g b forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose ((g a -> g b) -> f (g a) -> f (g 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) -> 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 )f (g a) x )a a <$ :: forall a b. a -> Compose f g b -> Compose f g a <$ (Compose f (g b) x )=f (g a) -> Compose f g a forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose ((g b -> g a) -> f (g b) -> f (g a) forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (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 <$ )f (g b) x )-- | @since 4.9.0.0instance(Foldable f ,Foldable g )=>Foldable (Compose f g )wherefoldMap :: forall m a. Monoid m => (a -> m) -> Compose f g a -> m foldMap a -> m f (Compose f (g a) t )=(g a -> m) -> f (g 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) -> 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 )f (g a) t -- | @since 4.9.0.0instance(Traversable f ,Traversable g )=>Traversable (Compose f g )wheretraverse :: forall (f :: * -> *) a b. Applicative f => (a -> f b) -> Compose f g a -> f (Compose f g b) traverse a -> f b f (Compose f (g a) t )=f (g b) -> Compose f g b forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose (f (g b) -> Compose f g b) -> f (f (g b)) -> f (Compose f g b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (g a -> f (g b)) -> f (g a) -> f (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) -> f a -> f (f b) traverse ((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 )f (g a) t -- | @since 4.9.0.0instance(Applicative f ,Applicative g )=>Applicative (Compose f g )wherepure :: forall a. a -> Compose f g a pure a x =f (g a) -> Compose f g a forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose (g a -> f (g a) forall a. a -> f a forall (f :: * -> *) a. Applicative f => a -> f a pure (a -> g a forall a. a -> g a forall (f :: * -> *) a. Applicative f => a -> f a pure a x ))Compose f (g (a -> b)) f <*> :: forall a b. Compose f g (a -> b) -> Compose f g a -> Compose f g b <*> Compose f (g a) x =f (g b) -> Compose f g b forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose ((g (a -> b) -> g a -> g b) -> f (g (a -> b)) -> f (g a) -> 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 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 (<*>) f (g (a -> b)) f f (g a) x )liftA2 :: forall a b c. (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c liftA2 a -> b -> c f (Compose f (g a) x )(Compose f (g b) y )=f (g c) -> Compose f g c forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose ((g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g 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) -> 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 )f (g a) x f (g b) y )-- | @since 4.9.0.0instance(Alternative f ,Applicative g )=>Alternative (Compose f g )whereempty :: forall a. Compose f g a empty =f (g a) -> Compose f g a forall {k} {k} (f :: k -> *) (g :: k -> k) (a :: k). f (g a) -> Compose f g a Compose f (g a) forall a. f a forall (f :: * -> *) a. Alternative f => f a empty <|> :: forall a. Compose f g a -> Compose f g a -> Compose f g a (<|>) =(f (g a) -> f (g a) -> f (g a)) -> Compose f g a -> Compose f g a -> Compose f g a forall a b. Coercible a b => a -> b coerce (f (g a) -> f (g a) -> f (g a) forall a. f a -> f a -> f a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a (<|>) ::f (g a )->f (g a )->f (g a ))::foralla .Compose f g a ->Compose f g a ->Compose f g a -- | The deduction (via generativity) that if @g x :~: g y@ then @x :~: y@.---- @since 4.14.0.0instance(TestEquality f )=>TestEquality (Compose f g )wheretestEquality :: forall (a :: k) (b :: k). Compose f g a -> Compose f g b -> Maybe (a :~: b) testEquality (Compose f (g a) x )(Compose f (g b) y )=casef (g a) -> f (g b) -> Maybe (g a :~: g b) forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b) forall {k} (f :: k -> *) (a :: k) (b :: k). TestEquality f => f a -> f b -> Maybe (a :~: b) testEquality f (g a) x f (g b) y of-- :: Maybe (g x :~: g y)Just g a :~: g b Refl ->(a :~: b) -> Maybe (a :~: b) forall a. a -> Maybe a Just a :~: a a :~: b forall {k} (a :: k). a :~: a Refl -- :: Maybe (x :~: y)Maybe (g a :~: g b) Nothing ->Maybe (a :~: b) forall a. Maybe a Nothing