{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE Safe #-} {-# LANGUAGE StandaloneDeriving #-} module Data.Functor.Sum ( Sum(..), ) where import Control.Applicative ((<|>)) import GHC.Internal.Data.Data (Data) import Data.Functor.Classes import GHC.Generics (Generic, Generic1) import Prelude data Sum f g a = InL (f a) | InR (g a) deriving ( Typeable (Sum f g a) Typeable (Sum f g a) => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum f g a -> c (Sum f g a)) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum f g a)) -> (Sum f g a -> Constr) -> (Sum f g a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a))) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum f g a))) -> ((forall b. Data b => b -> b) -> Sum f g a -> Sum f g a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r) -> (forall u. (forall d. Data d => d -> u) -> Sum f g a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> Sum f g a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a)) -> Data (Sum f g a) Sum f g a -> Constr Sum f g a -> DataType (forall b. Data b => b -> b) -> Sum f g a -> Sum 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) -> Sum f g a -> u forall u. (forall d. Data d => d -> u) -> Sum f g a -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum 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 (Sum 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)) => Sum 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)) => Sum 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) -> Sum f g a -> Sum 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) -> Sum 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) -> Sum 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') -> Sum 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') -> Sum 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) -> Sum f g a -> m (Sum 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) -> Sum f g a -> m (Sum 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 (Sum 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) -> Sum f g a -> c (Sum 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 (Sum 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 (Sum f g a)) forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum f g a) forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum f g a -> c (Sum f g a) forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a)) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum 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) -> Sum f g a -> c (Sum f g a) gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum f g a -> c (Sum 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 (Sum f g a) gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum 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)) => Sum f g a -> Constr toConstr :: Sum 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)) => Sum f g a -> DataType dataTypeOf :: Sum 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 (Sum f g a)) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum 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 (Sum f g a)) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum 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) -> Sum f g a -> Sum f g a gmapT :: (forall b. Data b => b -> b) -> Sum f g a -> Sum 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') -> Sum f g a -> r gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum 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') -> Sum f g a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum 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) -> Sum f g a -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> Sum 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) -> Sum f g a -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Sum 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) -> Sum f g a -> m (Sum f g a) gmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum 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) -> Sum f g a -> m (Sum f g a) gmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum 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) -> Sum f g a -> m (Sum f g a) gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) Data , (forall x. Sum f g a -> Rep (Sum f g a) x) -> (forall x. Rep (Sum f g a) x -> Sum f g a) -> Generic (Sum f g a) forall x. Rep (Sum f g a) x -> Sum f g a forall x. Sum f g a -> Rep (Sum 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 (Sum f g a) x -> Sum f g a forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Sum f g a -> Rep (Sum f g a) x $cfrom :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Sum f g a -> Rep (Sum f g a) x from :: forall x. Sum f g a -> Rep (Sum f g a) x $cto :: forall k (f :: k -> *) (g :: k -> *) (a :: k) x. Rep (Sum f g a) x -> Sum f g a to :: forall x. Rep (Sum f g a) x -> Sum f g a Generic , (forall (a :: k). Sum f g a -> Rep1 (Sum f g) a) -> (forall (a :: k). Rep1 (Sum f g) a -> Sum f g a) -> Generic1 (Sum f g) forall (a :: k). Rep1 (Sum f g) a -> Sum f g a forall (a :: k). Sum f g a -> Rep1 (Sum 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 (Sum f g) a -> Sum f g a forall k (f :: k -> *) (g :: k -> *) (a :: k). Sum f g a -> Rep1 (Sum f g) a $cfrom1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). Sum f g a -> Rep1 (Sum f g) a from1 :: forall (a :: k). Sum f g a -> Rep1 (Sum f g) a $cto1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). Rep1 (Sum f g) a -> Sum f g a to1 :: forall (a :: k). Rep1 (Sum f g) a -> Sum f g a Generic1 ) deriving instance (Eq (f a), Eq (g a)) => Eq (Sum f g a) deriving instance (Ord (f a), Ord (g a)) => Ord (Sum f g a) deriving instance (Read (f a), Read (g a)) => Read (Sum f g a) deriving instance (Show (f a), Show (g a)) => Show (Sum f g a) instance (Eq1 f, Eq1 g) => Eq1 (Sum f g) where liftEq :: forall a b. (a -> b -> Bool) -> Sum f g a -> Sum f g b -> Bool liftEq a -> b -> Bool eq (InL f a x1) (InL f b x2) = (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 liftEq a -> b -> Bool _ (InL f a _) (InR g b _) = Bool False liftEq a -> b -> Bool _ (InR g a _) (InL f b _) = Bool False liftEq a -> b -> Bool eq (InR g a y1) (InR g b y2) = (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 instance (Ord1 f, Ord1 g) => Ord1 (Sum f g) where liftCompare :: forall a b. (a -> b -> Ordering) -> Sum f g a -> Sum f g b -> Ordering liftCompare a -> b -> Ordering comp (InL f a x1) (InL f b x2) = (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 liftCompare a -> b -> Ordering _ (InL f a _) (InR g b _) = Ordering LT liftCompare a -> b -> Ordering _ (InR g a _) (InL f b _) = Ordering GT liftCompare a -> b -> Ordering comp (InR g a y1) (InR g b y2) = (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 instance (Read1 f, Read1 g) => Read1 (Sum f g) where liftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) liftReadPrec ReadPrec a rp ReadPrec [a] rl = ReadPrec (Sum f g a) -> ReadPrec (Sum f g a) forall a. ReadPrec a -> ReadPrec a readData (ReadPrec (Sum f g a) -> ReadPrec (Sum f g a)) -> ReadPrec (Sum f g a) -> ReadPrec (Sum f g a) forall a b. (a -> b) -> a -> b $ ReadPrec (f a) -> String -> (f a -> Sum f g a) -> ReadPrec (Sum f g a) forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t readUnaryWith (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) String "InL" f a -> Sum f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a InL ReadPrec (Sum f g a) -> ReadPrec (Sum f g a) -> ReadPrec (Sum f g a) forall a. ReadPrec a -> ReadPrec a -> ReadPrec a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> ReadPrec (g a) -> String -> (g a -> Sum f g a) -> ReadPrec (Sum f g a) forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t readUnaryWith (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 "InR" g a -> Sum f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a InR liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] liftReadListPrec = ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum 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 [Sum f g a] liftReadList = (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a] forall (f :: * -> *) a. Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] liftReadListDefault instance (Show1 f, Show1 g) => Show1 (Sum f g) where liftShowsPrec :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum f g a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl Int d (InL f a x) = (Int -> f a -> ShowS) -> String -> Int -> f a -> ShowS forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS showsUnaryWith ((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) String "InL" Int d f a x liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl Int d (InR g a y) = (Int -> g a -> ShowS) -> String -> Int -> g a -> ShowS forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS showsUnaryWith ((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 "InR" Int d g a y instance (Functor f, Functor g) => Functor (Sum f g) where fmap :: forall a b. (a -> b) -> Sum f g a -> Sum f g b fmap a -> b f (InL f a x) = f b -> Sum f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a InL ((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) fmap a -> b f (InR g a y) = g b -> Sum f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a InR ((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 -> Sum f g b -> Sum f g a <$ (InL f b x) = f a -> Sum f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a InL (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 <$ (InR g b y) = g a -> Sum f g a forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a InR (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) instance (Foldable f, Foldable g) => Foldable (Sum f g) where foldMap :: forall m a. Monoid m => (a -> m) -> Sum f g a -> m foldMap a -> m f (InL f a x) = (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 foldMap a -> m f (InR g a y) = (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 instance (Traversable f, Traversable g) => Traversable (Sum f g) where traverse :: forall (f :: * -> *) a b. Applicative f => (a -> f b) -> Sum f g a -> f (Sum f g b) traverse a -> f b f (InL f a x) = f b -> Sum f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (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 traverse a -> f b f (InR g a y) = g b -> Sum f g b forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (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
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4