bifunctors-5.2: Bifunctors

Copyright(C) 2008-2016 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Bifunctor.Joker

Description

From the Functional Pearl "Clowns to the Left of me, Jokers to the Right: Dissecting Data Structures" by Conor McBride.

Synopsis

Documentation

newtype Joker g a b Source

Make a Functor over the second argument of a Bifunctor.

Mnemonic: Clowns to the left (parameter of the Bifunctor), jokers to the right.

Constructors

Joker 

Fields

Instances

Functor g => Bifunctor (Joker * * g) Source 

Methods

bimap :: (a -> b) -> (c -> d) -> Joker * * g a c -> Joker * * g b d

first :: (a -> b) -> Joker * * g a c -> Joker * * g b c

second :: (b -> c) -> Joker * * g a b -> Joker * * g a c

Foldable g => Bifoldable (Joker * * g) Source 

Methods

bifold :: Monoid m => Joker * * g m m -> m Source

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Joker * * g a b -> m Source

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Joker * * g a b -> c Source

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Joker * * g a b -> c Source

Traversable g => Bitraversable (Joker * * g) Source 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Joker * * g a b -> f (Joker * * g c d) Source

Applicative g => Biapplicative (Joker * * g) Source 

Methods

bipure :: a -> b -> Joker * * g a b Source

(<<*>>) :: Joker * * g (a -> b) (c -> d) -> Joker * * g a c -> Joker * * g b d Source

(*>>) :: Joker * * g a b -> Joker * * g c d -> Joker * * g c d Source

(<<*) :: Joker * * g a b -> Joker * * g c d -> Joker * * g a b Source

Functor g => Functor (Joker k * g a) Source 

Methods

fmap :: (b -> c) -> Joker k * g a b -> Joker k * g a c

(<$) :: b -> Joker k * g a c -> Joker k * g a b

Foldable g => Foldable (Joker k * g a) Source 

Methods

fold :: Monoid m => Joker k * g a m -> m

foldMap :: Monoid m => (b -> m) -> Joker k * g a b -> m

foldr :: (b -> c -> c) -> c -> Joker k * g a b -> c

foldr' :: (b -> c -> c) -> c -> Joker k * g a b -> c

foldl :: (b -> c -> b) -> b -> Joker k * g a c -> b

foldl' :: (b -> c -> b) -> b -> Joker k * g a c -> b

foldr1 :: (b -> b -> b) -> Joker k * g a b -> b

foldl1 :: (b -> b -> b) -> Joker k * g a b -> b

toList :: Joker k * g a b -> [b]

null :: Joker k * g a b -> Bool

length :: Joker k * g a b -> Int

elem :: Eq b => b -> Joker k * g a b -> Bool

maximum :: Ord b => Joker k * g a b -> b

minimum :: Ord b => Joker k * g a b -> b

sum :: Num b => Joker k * g a b -> b

product :: Num b => Joker k * g a b -> b

Traversable g => Traversable (Joker k * g a) Source 

Methods

traverse :: Applicative f => (b -> f c) -> Joker k * g a b -> f (Joker k * g a c)

sequenceA :: Applicative f => Joker k * g a (f b) -> f (Joker k * g a b)

mapM :: Monad m => (b -> m c) -> Joker k * g a b -> m (Joker k * g a c)

sequence :: Monad m => Joker k * g a (m b) -> m (Joker k * g a b)

Generic1 (Joker k * g a) Source 

Associated Types

type Rep1 (Joker k * g a :: * -> *) :: * -> *

Methods

from1 :: Joker k * g a b -> Rep1 (Joker k * g a) b

to1 :: Rep1 (Joker k * g a) b -> Joker k * g a b

Eq (g b) => Eq (Joker k k g a b) Source 

Methods

(==) :: Joker k k g a b -> Joker k k g a b -> Bool

(/=) :: Joker k k g a b -> Joker k k g a b -> Bool

Ord (g b) => Ord (Joker k k g a b) Source 

Methods

compare :: Joker k k g a b -> Joker k k g a b -> Ordering

(<) :: Joker k k g a b -> Joker k k g a b -> Bool

(<=) :: Joker k k g a b -> Joker k k g a b -> Bool

(>) :: Joker k k g a b -> Joker k k g a b -> Bool

(>=) :: Joker k k g a b -> Joker k k g a b -> Bool

max :: Joker k k g a b -> Joker k k g a b -> Joker k k g a b

min :: Joker k k g a b -> Joker k k g a b -> Joker k k g a b

Read (g b) => Read (Joker k k g a b) Source 

Methods

readsPrec :: Int -> ReadS (Joker k k g a b)

readList :: ReadS [Joker k k g a b]

readPrec :: ReadPrec (Joker k k g a b)

readListPrec :: ReadPrec [Joker k k g a b]

Show (g b) => Show (Joker k k g a b) Source 

Methods

showsPrec :: Int -> Joker k k g a b -> ShowS

show :: Joker k k g a b -> String

showList :: [Joker k k g a b] -> ShowS

Generic (Joker k k g a b) Source 

Associated Types

type Rep (Joker k k g a b) :: * -> *

Methods

from :: Joker k k g a b -> Rep (Joker k k g a b) x

to :: Rep (Joker k k g a b) x -> Joker k k g a b

type Rep1 (Joker k k1 g a) Source 
type Rep (Joker k k1 g a b) Source