Safe Haskell | None |
---|---|
Language | Haskell2010 |
- _1 :: Functor f => LensLike f (a, b) (a', b) a a'
- _2 :: Functor f => LensLike f (a, b) (a, b') b b'
- chosen :: Functor f => LensLike f (Either a a) (Either b b) a b
- ix :: Eq k => k -> Lens' (k -> v) v
- at :: Ord k => k -> Lens' (Map k v) (Maybe v)
- intAt :: Int -> Lens' (IntMap v) (Maybe v)
- contains :: Ord k => k -> Lens' (Set k) Bool
- intContains :: Int -> Lens' IntSet Bool
- both :: Applicative f => LensLike f (a, a) (b, b) a b
- _Left :: Applicative f => LensLike f (Either a b) (Either a' b) a a'
- _Right :: Applicative f => LensLike f (Either a b) (Either a b') b b'
- _Just :: Applicative f => LensLike f (Maybe a) (Maybe a') a a'
- _Nothing :: Applicative f => LensLike' f (Maybe a) ()
- ignored :: Applicative f => LensLike f a a b b'
- to :: Phantom f => (a -> b) -> LensLike f a a' b b'
- view :: FoldLike b a a' b b' -> a -> b
- (^.) :: a -> FoldLike b a a' b b' -> b
- folding :: (Foldable g, Phantom f, Applicative f) => (a -> g b) -> LensLike f a a' b b'
- views :: FoldLike r a a' b b' -> (b -> r) -> a -> r
- (^..) :: a -> FoldLike [b] a a' b b' -> [b]
- (^?) :: a -> FoldLike (First b) a a' b b' -> Maybe b
- toListOf :: FoldLike [b] a a' b b' -> a -> [b]
- allOf :: FoldLike All a a' b b' -> (b -> Bool) -> a -> Bool
- anyOf :: FoldLike Any a a' b b' -> (b -> Bool) -> a -> Bool
- firstOf :: FoldLike (First b) a a' b b' -> a -> Maybe b
- lastOf :: FoldLike (Last b) a a' b b' -> a -> Maybe b
- sumOf :: Num b => FoldLike (Sum b) a a' b b' -> a -> b
- productOf :: Num b => FoldLike (Product b) a a' b b' -> a -> b
- lengthOf :: Num r => FoldLike (Sum r) a a' b b' -> a -> r
- nullOf :: FoldLike All a a' b b' -> a -> Bool
- backwards :: LensLike (Backwards f) a a' b b' -> LensLike f a a' b b'
- over :: ASetter a a' b b' -> (b -> b') -> a -> a'
- (%~) :: ASetter a a' b b' -> (b -> b') -> a -> a'
- set :: ASetter a a' b b' -> b' -> a -> a'
- (.~) :: ASetter a a' b b' -> b' -> a -> a'
- (&) :: a -> (a -> b) -> b
- (+~) :: Num b => ASetter' a b -> b -> a -> a
- (*~) :: Num b => ASetter' a b -> b -> a -> a
- (-~) :: Num b => ASetter' a b -> b -> a -> a
- (//~) :: Fractional b => ASetter' a b -> b -> a -> a
- (&&~) :: ASetter' a Bool -> Bool -> a -> a
- (||~) :: ASetter' a Bool -> Bool -> a -> a
- (<>~) :: Monoid o => ASetter' a o -> o -> a -> a
- zoom :: Monad m => LensLike' (Zooming m c) a b -> StateT b m c -> StateT a m c
- use :: MonadState a m => FoldLike b a a' b b' -> m b
- uses :: MonadState a m => FoldLike r a a' b b' -> (b -> r) -> m r
- (%=) :: MonadState a m => Setter a a b b' -> (b -> b') -> m ()
- assign :: MonadState a m => Setter a a b b' -> b' -> m ()
- (.=) :: MonadState a m => Setter a a b b' -> b' -> m ()
- (%%=) :: MonadState a m => LensLike (Writer c) a a b b' -> (b -> (c, b')) -> m c
- (<~) :: MonadState a m => Setter a a b b' -> m b' -> m ()
- (+=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (-=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (*=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (//=) :: (MonadState a m, Fractional b) => Setter' a b -> b -> m ()
- (&&=) :: MonadState a m => Setter' a Bool -> Bool -> m ()
- (||=) :: MonadState a m => Setter' a Bool -> Bool -> m ()
- (<>=) :: (Monoid o, MonadState a m) => Setter' a o -> o -> m ()
- mapped :: Functor f => Setter (f a) (f a') a a'
- lens :: (a -> b) -> (a -> b' -> a') -> Lens a a' b b'
- iso :: (a -> b) -> (b' -> a') -> Lens a a' b b'
- setting :: ((b -> b') -> a -> a') -> Setter a a' b b'
- choosing :: Functor f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (Either a b) (Either a' b') c c'
- alongside :: Functor f => LensLike (AlongsideLeft f b2') a1 a1' b1 b1' -> LensLike (AlongsideRight f a1') a2 a2' b2 b2' -> LensLike f (a1, a2) (a1', a2') (b1, b2) (b1', b2')
- beside :: Applicative f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (a, b) (a', b') c c'
- makeLenses :: Name -> Q [Dec]
- makeTraversals :: Name -> Q [Dec]
- makeLensesBy :: (String -> Maybe String) -> Name -> Q [Dec]
- makeLensesFor :: [(String, String)] -> Name -> Q [Dec]
- type LensLike f a a' b b' = (b -> f b') -> a -> f a'
- type LensLike' f a b = (b -> f b) -> a -> f a
- type FoldLike r a a' b b' = LensLike (Constant r) a a' b b'
- type FoldLike' r a b = LensLike' (Constant r) a b
- type ASetter a a' b b' = LensLike Identity a a' b b'
- type ASetter' a b = LensLike' Identity a b
- class Functor f => Phantom f
- data Constant a b :: * -> * -> *
- data Identity a :: * -> *
- data AlongsideLeft f b a :: (* -> *) -> * -> * -> *
- data AlongsideRight f a b :: (* -> *) -> * -> * -> *
- data Zooming m c a :: (* -> *) -> * -> * -> *
- class Functor f => Applicative f
- class Foldable t
- class Monoid a where
- (<>) :: Monoid m => m -> m -> m
- data Backwards f a :: (* -> *) -> * -> *
- data All :: *
- data Any :: *
- data First a :: * -> *
- data Last a :: * -> *
- data Sum a :: * -> *
- data Product a :: * -> *
- data StateT s m a :: * -> (* -> *) -> * -> *
- type Writer w = WriterT w Identity
Stock Lenses
chosen :: Functor f => LensLike f (Either a a) (Either b b) a b
Lens on the Left or Right element of an (Either
a a).
Stock Traversals
both :: Applicative f => LensLike f (a, a) (b, b) a b
Traversals on both elements of a pair (a,a)
.
_Left :: Applicative f => LensLike f (Either a b) (Either a' b) a a'
_Right :: Applicative f => LensLike f (Either a b) (Either a b') b b'
_Just :: Applicative f => LensLike f (Maybe a) (Maybe a') a a'
ignored :: Applicative f => LensLike f a a b b'
The empty traveral on any type.
Basic lens combinators
to :: Phantom f => (a -> b) -> LensLike f a a' b b'
to :: (a -> b) -> Getter a a' b b'
to
promotes a projection function to a read-only lens called a getter.
To demote a lens to a projection function, use the section (^.l)
or view l
.
>>>
(3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0
view :: FoldLike b a a' b b' -> a -> b
view :: Getter a a' b b' -> a -> b
Demote a lens or getter to a projection function.
view :: Monoid b => Fold a a' b b' -> a -> b
Returns the monoidal summary of a traversal or a fold.
(^.) :: a -> FoldLike b a a' b b' -> b infixl 8
(^.) :: a -> Getter a a' b b' -> b
Access the value referenced by a getter or lens.
(^.) :: Monoid b => a -> Fold a a' b b' -> b
Access the monoidal summary referenced by a getter or lens.
folding :: (Foldable g, Phantom f, Applicative f) => (a -> g b) -> LensLike f a a' b b'
folding :: (a -> [b]) -> Fold a a' b b'
folding
promotes a "toList" function to a read-only traversal called a fold.
To demote a traversal or fold to a "toList" function use the section (^..l)
or toListOf l
.
views :: FoldLike r a a' b b' -> (b -> r) -> a -> r
views :: Monoid r => Fold a a' b b' -> (b -> r) -> a -> r
Given a fold or traversal, return the foldMap
of all the values using the given function.
views :: Getter a a' b b' -> (b -> r) -> a -> r
views
is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.
views l f a = f (view l a)
(^..) :: a -> FoldLike [b] a a' b b' -> [b] infixl 8
(^..) :: a -> Getter a a' b b' -> [b]
Returns a list of all of the referenced values in order.
toListOf :: FoldLike [b] a a' b b' -> a -> [b]
toListOf :: Fold a a' b b' -> a -> [b]
Returns a list of all of the referenced values in order.
allOf :: FoldLike All a a' b b' -> (b -> Bool) -> a -> Bool
allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool
Returns true if all of the referenced values satisfy the given predicate.
anyOf :: FoldLike Any a a' b b' -> (b -> Bool) -> a -> Bool
anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool
Returns true if any of the referenced values satisfy the given predicate.
sumOf :: Num b => FoldLike (Sum b) a a' b b' -> a -> b
sumOf :: Num b => Fold a a' b b' -> a -> b
Returns the sum of all the referenced values.
productOf :: Num b => FoldLike (Product b) a a' b b' -> a -> b
productOf :: Num b => Fold a a' b b' -> a -> b
Returns the product of all the referenced values.
lengthOf :: Num r => FoldLike (Sum r) a a' b b' -> a -> r
lengthOf :: Num r => Fold a a' b b' -> a -> r
Counts the number of references in a traversal or fold for the input.
nullOf :: FoldLike All a a' b b' -> a -> Bool
nullOf :: Fold a a' b b' -> a -> Bool
Returns true if the number of references in the input is zero.
backwards :: LensLike (Backwards f) a a' b b' -> LensLike f a a' b b'
backwards :: Traversal a a' b b' -> Traversal a a' b b' backwards :: Fold a a' b b' -> Fold a a' b b'
Given a traversal or fold, reverse the order that elements are traversed.
backwards :: Lens a a' b b' -> Lens a a' b b' backwards :: Getter a a' b b' -> Getter a a' b b' backwards :: Setter a a' b b' -> Setter a a' b b'
No effect on lenses, getters or setters.
(&) :: a -> (a -> b) -> b infixl 1
Pseudo-imperatives
(//~) :: Fractional b => ASetter' a b -> b -> a -> a infixr 4
(<>~) :: Monoid o => ASetter' a o -> o -> a -> a infixr 4
Monoidally append a value to all referenced fields.
State related combinators
zoom :: Monad m => LensLike' (Zooming m c) a b -> StateT b m c -> StateT a m c
zoom :: Monad m => Lens' a b -> StateT b m c -> StateT a m c
Lift a stateful operation on a field to a stateful operation on the whole state. This is a good way to call a "subroutine" that only needs access to part of the state.
zoom :: (Monoid c, Moand m) => Traversal' a b -> StateT b m c -> StateT a m c
Run the "subroutine" on each element of the traversal in turn and mconcat
all the results together.
zoom :: Monad m => Traversal' a b -> StateT b m () -> StateT a m ()
Run the "subroutine" on each element the traversal in turn.
use :: MonadState a m => FoldLike b a a' b b' -> m b
use :: MonadState a m => Getter a a' b b' -> m b
Retrieve a field of the state
use :: (Monoid b, MonadState a m) => Fold a a' b b' -> m b
Retrieve a monoidal summary of all the referenced fields from the state
uses :: MonadState a m => FoldLike r a a' b b' -> (b -> r) -> m r
uses :: (MonadState a m, Monoid r) => Fold a a' b b' -> (b -> r) -> m r
Retrieve all the referenced fields from the state and foldMap the results together with f :: b -> r
.
uses :: MonadState a m => Getter a a' b b' -> (b -> r) -> m r
Retrieve a field of the state and pass it through the function f :: b -> r
.
uses l f = f <$> use l
(%=) :: MonadState a m => Setter a a b b' -> (b -> b') -> m () infix 4
Modify a field of the state.
assign :: MonadState a m => Setter a a b b' -> b' -> m ()
Set a field of the state.
(.=) :: MonadState a m => Setter a a b b' -> b' -> m () infix 4
Set a field of the state.
(%%=) :: MonadState a m => LensLike (Writer c) a a b b' -> (b -> (c, b')) -> m c infix 4
(%%=) :: MonadState a m => Lens a a b b' -> (b -> (c, b')) -> m c
Modify a field of the state while returning another value.
(%%=) :: (MonadState a m, Monoid c) => Traversal a a b b' -> (b -> (c, b')) -> m c
Modify each field of the state and return the mconcat
of the other values.
(<~) :: MonadState a m => Setter a a b b' -> m b' -> m () infixr 2
Set a field of the state using the result of executing a stateful command.
Compound state assignments
(+=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4
(-=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4
(*=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4
(//=) :: (MonadState a m, Fractional b) => Setter' a b -> b -> m () infixr 4
(&&=) :: MonadState a m => Setter' a Bool -> Bool -> m () infixr 4
(||=) :: MonadState a m => Setter' a Bool -> Bool -> m () infixr 4
(<>=) :: (Monoid o, MonadState a m) => Setter' a o -> o -> m () infixr 4
Monoidally append a value to all referenced fields of the state.
Stock Semantic Editor Combinators
Lens formers
:: (a -> b) | getter |
-> (a -> b' -> a') | setter |
-> Lens a a' b b' |
Build a lens from a getter
and setter
families.
Caution: In order for the generated lens family to be well-defined, you must ensure that the three lens laws hold:
getter (setter a b) === b
setter a (getter a) === a
setter (setter a b1) b2) === setter a b2
:: (a -> b) | yin |
-> (b' -> a') | yang |
-> Lens a a' b b' |
Build a lens from isomorphism families.
Caution: In order for the generated lens family to be well-defined, you must ensure that the two isomorphism laws hold:
yin . yang === id
yang . yin === id
:: ((b -> b') -> a -> a') | sec (semantic editor combinator) |
-> Setter a a' b b' |
setting
promotes a "semantic editor combinator" to a modify-only lens.
To demote a lens to a semantic edit combinator, use the section (l %~)
or over l
from Lens.Family2.
>>>
setting map . fstL %~ length $ [("The",0),("quick",1),("brown",1),("fox",2)]
[(3,0),(5,1),(5,1),(3,2)]
Caution: In order for the generated setter family to be well-defined, you must ensure that the two functors laws hold:
sec id === id
sec f . sec g === sec (f . g)
Combining Combinators
choosing :: Functor f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (Either a b) (Either a' b') c c'
choosing :: Lens a a' c c' -> Lens b b' c c' -> Lens (Either a b) (Either a' b') c c'
choosing :: Traversal a a' c c' -> Traversal b b' c c' -> Traversal (Either a b) (Either a' b') c c'
choosing :: Getter a a' c c' -> Getter b b' c c' -> Getter (Either a b) (Either a' b') c c'
choosing :: Fold a a' c c' -> Fold b b' c c' -> Fold (Either a b) (Either a' b') c c'
choosing :: Setter a a' c c' -> Setter b b' c c' -> Setter (Either a b) (Either a' b') c c'
Given two lens/traversal/getter/fold/setter families with the same substructure, make a new lens/traversal/getter/fold/setter on Either
.
alongside :: Functor f => LensLike (AlongsideLeft f b2') a1 a1' b1 b1' -> LensLike (AlongsideRight f a1') a2 a2' b2 b2' -> LensLike f (a1, a2) (a1', a2') (b1, b2) (b1', b2')
alongside :: Lens a1 a1' b1 b1' -> Lens a2 a2' b2 b2' -> Lens (a1, a2) (a1', a2') (b1, b2) (b1', b2')
alongside :: Getter a1 a1' b1 b1' -> Getter a2 a2' b2 b2' -> Getter (a1, a2) (a1', a2') (b1, b2) (b1', b2')
Given two lens/getter families, make a new lens/getter on their product.
beside :: Applicative f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (a, b) (a', b') c c'
beside :: Traversal a a' c c' -> Traversal b' b' c c' -> Traversal (a,b) (a',b') c c'
beside :: Fold a a' c c' -> Fold b' b' c c' -> Fold (a,b) (a',b') c c'
beside :: Setter a a' c c' -> Setter b' b' c c' -> Setter (a,b) (a',b') c c'
Given two traversals/folds/setters referencing a type c
, create a traversal/fold/setter on the pair referencing c
.
TH incantations
makeLenses :: Name -> Q [Dec]
Derive lenses for the record selectors in a single-constructor data declaration, or for the record selector in a newtype declaration. Lenses will only be generated for record fields which are prefixed with an underscore.
Example usage:
$(makeLenses ''Foo)
makeTraversals :: Name -> Q [Dec]
Derive traversals for each constructor in a data or newtype declaration, Traversals will be named by prefixing the constructor name with an underscore.
Example usage:
$(makeTraversals ''Foo)
makeLensesBy :: (String -> Maybe String) -> Name -> Q [Dec]
Derive lenses with the provided name transformation
and filtering function. Produce Just lensName
to generate a lens
of the resultant name, or Nothing
to not generate a lens
for the input record name.
Example usage:
$(makeLensesBy (\n -> Just (n ++ "L")) ''Foo)
makeLensesFor :: [(String, String)] -> Name -> Q [Dec]
Derive lenses, specifying explicit pairings of (fieldName, lensName)
.
Example usage:
$(makeLensesFor [("_foo", "fooLens"), ("bar", "lbar")] ''Foo)
Types
type LensLike f a a' b b' = (b -> f b') -> a -> f a'
type LensLike' f a b = (b -> f b) -> a -> f a
coerce
data Constant a b :: * -> * -> *
Constant functor.
Functor (Constant a) | |
Monoid a => Applicative (Constant a) | |
Foldable (Constant a) | |
Traversable (Constant a) | |
Phantom (Constant a) | |
Eq a => Eq1 (Constant a) | |
Ord a => Ord1 (Constant a) | |
Read a => Read1 (Constant a) | |
Show a => Show1 (Constant a) | |
Eq a => Eq (Constant a b) | |
Ord a => Ord (Constant a b) | |
Read a => Read (Constant a b) | |
Show a => Show (Constant a b) |
data Identity a :: * -> *
Identity functor and monad. (a non-strict monad)
Since: 4.8.0.0
Monad Identity | |
Functor Identity | |
MonadFix Identity | |
Applicative Identity | |
Foldable Identity | |
Traversable Identity | |
Generic1 Identity | |
MonadZip Identity | |
Eq a => Eq (Identity a) | |
Data a => Data (Identity a) | |
Ord a => Ord (Identity a) | |
Read a => Read (Identity a) | This instance would be equivalent to the derived instances of the
|
Show a => Show (Identity a) | This instance would be equivalent to the derived instances of the
|
Generic (Identity a) | |
type Rep1 Identity = D1 D1Identity (C1 C1_0Identity (S1 S1_0_0Identity Par1)) | |
type Rep (Identity a) = D1 D1Identity (C1 C1_0Identity (S1 S1_0_0Identity (Rec0 a))) |
data AlongsideLeft f b a :: (* -> *) -> * -> * -> *
Functor f => Functor (AlongsideLeft f a) | |
Phantom f => Phantom (AlongsideLeft f a) |
data AlongsideRight f a b :: (* -> *) -> * -> * -> *
Functor f => Functor (AlongsideRight f a) | |
Phantom f => Phantom (AlongsideRight f a) |
data Zooming m c a :: (* -> *) -> * -> * -> *
Re-exports
class Functor f => Applicative f
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Applicative [] | |
Applicative IO | |
Applicative Q | |
Applicative Identity | |
Applicative First | |
Applicative Last | |
Applicative Maybe | |
Applicative ((->) a) | |
Applicative (Either e) | |
Monoid a => Applicative ((,) a) | |
Applicative (Proxy *) | |
Applicative f => Applicative (Backwards f) | Apply |
Monoid a => Applicative (Constant a) | |
Applicative f => Applicative (Alt * f) | |
(Functor m, Monad m) => Applicative (StateT s m) | |
(Monoid c, Monad m) => Applicative (Zooming m c) | |
(Functor m, Monad m) => Applicative (ErrorT e m) | |
(Monoid w, Applicative m) => Applicative (WriterT w m) |
class Foldable t
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
Foldable [] | |
Foldable Identity | |
Foldable Maybe | |
Foldable IntMap | |
Foldable Set | |
Foldable (Either a) | |
Foldable ((,) a) | |
Ix i => Foldable (Array i) | |
Foldable (Proxy *) | |
Foldable (Map k) | |
Foldable f => Foldable (Backwards f) | Derived instance. |
Foldable (Constant a) | |
Foldable f => Foldable (ErrorT e f) | |
Foldable f => Foldable (WriterT w f) |
class Monoid a where
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
mempty :: a
Identity of mappend
mappend :: a -> a -> a
An associative operation
mconcat :: [a] -> a
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Monoid Ordering | |
Monoid () | |
Monoid All | |
Monoid Any | |
Monoid IntSet | |
Monoid Doc | |
Monoid [a] | |
Ord a => Monoid (Max a) | |
Ord a => Monoid (Min a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid (IntMap a) | |
Ord a => Monoid (Set a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid (Proxy k s) | |
Ord k => Monoid (Map k v) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
Alternative f => Monoid (Alt * f a) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) |
data Backwards f a :: (* -> *) -> * -> *
The same functor, but with an Applicative
instance that performs
actions in the reverse order.
Functor f => Functor (Backwards f) | Derived instance. |
Applicative f => Applicative (Backwards f) | Apply |
Foldable f => Foldable (Backwards f) | Derived instance. |
Traversable f => Traversable (Backwards f) | Derived instance. |
Alternative f => Alternative (Backwards f) | Try alternatives in the same order as |
Phantom f => Phantom (Backwards f) | |
Eq1 f => Eq1 (Backwards f) | |
Ord1 f => Ord1 (Backwards f) | |
Read1 f => Read1 (Backwards f) | |
Show1 f => Show1 (Backwards f) | |
(Eq1 f, Eq a) => Eq (Backwards f a) | |
(Ord1 f, Ord a) => Ord (Backwards f a) | |
(Read1 f, Read a) => Read (Backwards f a) | |
(Show1 f, Show a) => Show (Backwards f a) |
data First a :: * -> *
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
Monad First | |
Functor First | |
Applicative First | |
Generic1 First | |
Eq a => Eq (First a) | |
Ord a => Ord (First a) | |
Read a => Read (First a) | |
Show a => Show (First a) | |
Generic (First a) | |
Monoid (First a) | |
type Rep1 First = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec1 Maybe))) | |
type Rep (First a) = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec0 (Maybe a)))) |
data Last a :: * -> *
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last
a
, and thus to
Dual
(First
a)Dual
(Alt
Maybe
a)
Monad Last | |
Functor Last | |
Applicative Last | |
Generic1 Last | |
Eq a => Eq (Last a) | |
Ord a => Ord (Last a) | |
Read a => Read (Last a) | |
Show a => Show (Last a) | |
Generic (Last a) | |
Monoid (Last a) | |
type Rep1 Last = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec1 Maybe))) | |
type Rep (Last a) = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec0 (Maybe a)))) |
data Sum a :: * -> *
Monoid under addition.
Generic1 Sum | |
Bounded a => Bounded (Sum a) | |
Eq a => Eq (Sum a) | |
Num a => Num (Sum a) | |
Ord a => Ord (Sum a) | |
Read a => Read (Sum a) | |
Show a => Show (Sum a) | |
Generic (Sum a) | |
Num a => Monoid (Sum a) | |
type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) | |
type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) |
data Product a :: * -> *
Monoid under multiplication.
Generic1 Product | |
Bounded a => Bounded (Product a) | |
Eq a => Eq (Product a) | |
Num a => Num (Product a) | |
Ord a => Ord (Product a) | |
Read a => Read (Product a) | |
Show a => Show (Product a) | |
Generic (Product a) | |
Num a => Monoid (Product a) | |
type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) | |
type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a))) |
data StateT s m a :: * -> (* -> *) -> * -> *
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Monad m => MonadState s (StateT s m) | |
MonadTrans (StateT s) | |
Monad m => Monad (StateT s m) | |
Functor m => Functor (StateT s m) | |
MonadFix m => MonadFix (StateT s m) | |
(Functor m, Monad m) => Applicative (StateT s m) | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |
MonadIO m => MonadIO (StateT s m) |