| Copyright | Samuel Schlesinger 2021 (c) |
|---|---|
| License | MIT |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Merge
Description
Synopsis
- data Validation e a
- validation :: (e -> r) -> (a -> r) -> Validation e a -> r
- newtype Merge e x a = Merge {
- runMerge :: x -> x -> Validation e a
- merge :: (x -> x -> Validation e a) -> Merge e x a
- optional :: (Monoid e, Eq a) => (x -> Maybe a) -> Merge e x (Maybe a)
- required :: forall e a x. (Monoid e, Eq a) => (x -> a) -> Merge e x a
- combine :: forall e a x. Semigroup a => (x -> a) -> Merge e x a
- combineWith :: forall e a x. (a -> a -> a) -> (x -> a) -> Merge e x a
- (.?) :: Semigroup e => Merge e x a -> e -> Merge e x a
- (.!) :: Merge e x a -> (e -> e') -> Merge e' x a
- combineGen :: forall e a x s. Semigroup s => (a -> s) -> (s -> Validation e a) -> (x -> a) -> Merge e x a
- combineGenWith :: forall e a x s. (s -> s -> s) -> (a -> s) -> (s -> Validation e a) -> (x -> a) -> Merge e x a
- class Applicative f => Alternative (f :: Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- flattenValidation :: Merge e x (Validation e a) -> Merge e x a
- class Profunctor (p :: Type -> Type -> Type) where
- newtype Optional e a = Optional {
- unOptional :: Validation e (Maybe a)
- newtype Required e a = Required {
- unRequired :: Validation e a
- newtype Last a = Last {
- getLast :: a
- newtype First a = First {
- getFirst :: a
- newtype Product a = Product {
- getProduct :: a
- newtype Sum a = Sum {
- getSum :: a
- newtype Dual a = Dual {
- getDual :: a
- newtype Max a = Max {
- getMax :: a
- newtype Min a = Min {
- getMin :: a
A Validation Applicative
data Validation e a Source #
Like Either, but with an Applicative instance which
accumulates errors using their Semigroup operation.
Instances
validation :: (e -> r) -> (a -> r) -> Validation e a -> r Source #
The Merge type
Describes the merging of two values of the same type
into some other type. Represented as a Maybe valued
function, one can also think of this as a predicate
showing which pairs of values can be merged in this way.
data Example = Whatever { a :: Int, b :: Maybe Bool }
mergeExamples :: Merge Example Example
mergeExamples = Example <$> required a <*> optional bConstructors
| Merge | |
Fields
| |
Instances
| Profunctor (Merge e) Source # | |
Defined in Data.Merge Methods dimap :: (a -> b) -> (c -> d) -> Merge e b c -> Merge e a d # lmap :: (a -> b) -> Merge e b c -> Merge e a c # rmap :: (b -> c) -> Merge e a b -> Merge e a c # (#.) :: forall a b c q. Coercible c b => q b c -> Merge e a b -> Merge e a c # (.#) :: forall a b c q. Coercible b a => Merge e b c -> q a b -> Merge e a c # | |
| Functor (Merge e x) Source # | |
| Semigroup e => Applicative (Merge e x) Source # | |
| Monoid e => Alternative (Merge e x) Source # | |
| (Semigroup e, Semigroup a) => Semigroup (Merge e x a) Source # | |
| (Monoid e, Semigroup a) => Monoid (Merge e x a) Source # | |
Construction
merge :: (x -> x -> Validation e a) -> Merge e x a Source #
The most general combinator for constructing Merges.
optional :: (Monoid e, Eq a) => (x -> Maybe a) -> Merge e x (Maybe a) Source #
Meant to be used to merge optional fields in a record.
required :: forall e a x. (Monoid e, Eq a) => (x -> a) -> Merge e x a Source #
Meant to be used to merge required fields in a record.
combine :: forall e a x. Semigroup a => (x -> a) -> Merge e x a Source #
Associatively combine original fields of the record.
combineWith :: forall e a x. (a -> a -> a) -> (x -> a) -> Merge e x a Source #
Combine original fields of the record with the given function.
(.?) :: Semigroup e => Merge e x a -> e -> Merge e x a infixl 6 Source #
Appends some errors. Useful for the combinators provided by this library,
which use mempty to provide the default error type.
(.!) :: Merge e x a -> (e -> e') -> Merge e' x a Source #
Applies an arbitrary function to the error.
combineGen :: forall e a x s. Semigroup s => (a -> s) -> (s -> Validation e a) -> (x -> a) -> Merge e x a Source #
combineGen specialized to Semigroup operations.
combineGenWith :: forall e a x s. (s -> s -> s) -> (a -> s) -> (s -> Validation e a) -> (x -> a) -> Merge e x a Source #
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some and many should be the least solutions
of the equations:
Methods
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*> or liftA2. If it defines both, then they must behave
the same as their default definitions:
(<*>) =liftA2id
liftA2f x y = f<$>x<*>y
Further, any definition must satisfy the following:
- Identity
pureid<*>v = v- Composition
pure(.)<*>u<*>v<*>w = u<*>(v<*>w)- Homomorphism
puref<*>purex =pure(f x)- Interchange
u
<*>purey =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
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2p (liftA2q u v) =liftA2f u .liftA2g v
If f is also a Monad, it should satisfy
(which implies that pure and <*> satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
Using ApplicativeDo: 'fs ' can be understood as
the <*> asdo expression
do f <- fs a <- as pure (f a)
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
'as ' can be understood as the *> bsdo expression
do as bs
This is a tad complicated for our ApplicativeDo extension
which will give it a Monad constraint. For an Applicative
constraint we write it of the form
do _ <- as b <- bs pure b
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Using ApplicativeDo: 'as ' can be understood as
the <* bsdo expression
do a <- as bs pure a
Instances
| Applicative [] | Since: base-2.1 |
| Applicative Maybe | Since: base-2.1 |
| Applicative IO | Since: base-2.1 |
| Applicative Par1 | Since: base-4.9.0.0 |
| Applicative Complex | Since: base-4.9.0.0 |
| Applicative Min | Since: base-4.9.0.0 |
| Applicative Max | Since: base-4.9.0.0 |
| Applicative First | Since: base-4.9.0.0 |
| Applicative Last | Since: base-4.9.0.0 |
| Applicative Option | Since: base-4.9.0.0 |
| Applicative ZipList | f <$> ZipList xs1 <*> ... <*> ZipList xsN
= ZipList (zipWithN f xs1 ... xsN)where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
= ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
= ZipList {getZipList = ["a5","b6b6","c7c7c7"]}Since: base-2.1 |
| Applicative Identity | Since: base-4.8.0.0 |
| Applicative First | Since: base-4.8.0.0 |
| Applicative Last | Since: base-4.8.0.0 |
| Applicative Dual | Since: base-4.8.0.0 |
| Applicative Sum | Since: base-4.8.0.0 |
| Applicative Product | Since: base-4.8.0.0 |
| Applicative ReadPrec | Since: base-4.6.0.0 |
| Applicative ReadP | Since: base-4.6.0.0 |
| Applicative NonEmpty | Since: base-4.9.0.0 |
| Applicative Tree | |
| Applicative Seq | Since: containers-0.5.4 |
| Applicative P | Since: base-4.5.0.0 |
| Applicative (Either e) | Since: base-3.0 |
| Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)Since: base-2.1 |
| Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
| Arrow a => Applicative (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
| Semigroup e => Applicative (Validation e) Source # | |
Defined in Data.Merge Methods pure :: a -> Validation e a # (<*>) :: Validation e (a -> b) -> Validation e a -> Validation e b # liftA2 :: (a -> b -> c) -> Validation e a -> Validation e b -> Validation e c # (*>) :: Validation e a -> Validation e b -> Validation e b # (<*) :: Validation e a -> Validation e b -> Validation e a # | |
| Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
| (Monoid a, Monoid b) => Applicative ((,,) a b) | Since: base-4.14.0.0 |
| Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
| Applicative m => Applicative (Kleisli m a) | Since: base-4.14.0.0 |
Defined in Control.Arrow | |
| Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
| Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
| Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
| Applicative (Tagged s) | |
| Semigroup e => Applicative (Merge e x) Source # | |
| Applicative ((->) r :: Type -> Type) | Since: base-2.1 |
| Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
| (Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
| (Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) | Since: base-4.14.0.0 |
Defined in GHC.Base | |
| (Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
| Applicative f => Applicative (M1 i c f) | Since: base-4.9.0.0 |
| (Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
| (Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
Modification
flattenValidation :: Merge e x (Validation e a) -> Merge e x a Source #
class Profunctor (p :: Type -> Type -> Type) where #
Formally, the class Profunctor represents a profunctor
from Hask -> Hask.
Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.
You can define a Profunctor by either defining dimap or by defining both
lmap and rmap.
If you supply dimap, you should ensure that:
dimapidid≡id
If you supply lmap and rmap, ensure:
lmapid≡idrmapid≡id
If you supply both, you should also ensure:
dimapf g ≡lmapf.rmapg
These ensure by parametricity:
dimap(f.g) (h.i) ≡dimapg h.dimapf ilmap(f.g) ≡lmapg.lmapfrmap(f.g) ≡rmapf.rmapg
Instances
| Monad m => Profunctor (Kleisli m) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d # lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c # rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c # (#.) :: forall a b c q. Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c # (.#) :: forall a b c q. Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c # | |
| Profunctor (Tagged :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d # lmap :: (a -> b) -> Tagged b c -> Tagged a c # rmap :: (b -> c) -> Tagged a b -> Tagged a c # (#.) :: forall a b c q. Coercible c b => q b c -> Tagged a b -> Tagged a c # (.#) :: forall a b c q. Coercible b a => Tagged b c -> q a b -> Tagged a c # | |
| Profunctor (Merge e) Source # | |
Defined in Data.Merge Methods dimap :: (a -> b) -> (c -> d) -> Merge e b c -> Merge e a d # lmap :: (a -> b) -> Merge e b c -> Merge e a c # rmap :: (b -> c) -> Merge e a b -> Merge e a c # (#.) :: forall a b c q. Coercible c b => q b c -> Merge e a b -> Merge e a c # (.#) :: forall a b c q. Coercible b a => Merge e b c -> q a b -> Merge e a c # | |
| Profunctor ((->) :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe | |
| Functor w => Profunctor (Cokleisli w) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d # lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c # rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c # (#.) :: forall a b c q. Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c # (.#) :: forall a b c q. Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c # | |
| Functor f => Profunctor (Joker f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Joker f b c -> Joker f a d # lmap :: (a -> b) -> Joker f b c -> Joker f a c # rmap :: (b -> c) -> Joker f a b -> Joker f a c # (#.) :: forall a b c q. Coercible c b => q b c -> Joker f a b -> Joker f a c # (.#) :: forall a b c q. Coercible b a => Joker f b c -> q a b -> Joker f a c # | |
| Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Clown f b c -> Clown f a d # lmap :: (a -> b) -> Clown f b c -> Clown f a c # rmap :: (b -> c) -> Clown f a b -> Clown f a c # (#.) :: forall a b c q. Coercible c b => q b c -> Clown f a b -> Clown f a c # (.#) :: forall a b c q. Coercible b a => Clown f b c -> q a b -> Clown f a c # | |
| (Profunctor p, Profunctor q) => Profunctor (Sum p q) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Sum p q b c -> Sum p q a d # lmap :: (a -> b) -> Sum p q b c -> Sum p q a c # rmap :: (b -> c) -> Sum p q a b -> Sum p q a c # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Sum p q a b -> Sum p q a c # (.#) :: forall a b c q0. Coercible b a => Sum p q b c -> q0 a b -> Sum p q a c # | |
| (Profunctor p, Profunctor q) => Profunctor (Product p q) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d # lmap :: (a -> b) -> Product p q b c -> Product p q a c # rmap :: (b -> c) -> Product p q a b -> Product p q a c # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Product p q a b -> Product p q a c # (.#) :: forall a b c q0. Coercible b a => Product p q b c -> q0 a b -> Product p q a c # | |
| (Functor f, Profunctor p) => Profunctor (Tannen f p) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d # lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c # rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c # (#.) :: forall a b c q. Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c # (.#) :: forall a b c q. Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c # | |
| (Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d # lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c # rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c # (#.) :: forall a b c q. Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c # (.#) :: forall a b c q. Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c # | |
Useful Semigroups
This type's Semigroup instance encodes the simple,
deiscrete lattice generated by any given set.
Constructors
| Optional | |
Fields
| |
Instances
| (Eq e, Eq a) => Eq (Optional e a) Source # | |
| (Ord e, Ord a) => Ord (Optional e a) Source # | |
Defined in Data.Merge | |
| (Read e, Read a) => Read (Optional e a) Source # | |
| (Show e, Show a) => Show (Optional e a) Source # | |
| Generic (Optional e a) Source # | |
| (Monoid e, Eq a) => Semigroup (Optional e a) Source # | |
| (Monoid e, Eq a) => Monoid (Optional e a) Source # | |
| type Rep (Optional e a) Source # | |
Defined in Data.Merge type Rep (Optional e a) = D1 ('MetaData "Optional" "Data.Merge" "merge-0.3.1.1-9zHUzOVDGVrIUdM92Gcy6Q" 'True) (C1 ('MetaCons "Optional" 'PrefixI 'True) (S1 ('MetaSel ('Just "unOptional") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Validation e (Maybe a))))) | |
This type's Semigroup instance encodes the simple,
discrete lattice generated by any given set, excluding the
bottom.
Constructors
| Required | |
Fields
| |
Instances
| (Eq e, Eq a) => Eq (Required e a) Source # | |
| (Ord e, Ord a) => Ord (Required e a) Source # | |
Defined in Data.Merge | |
| (Read e, Read a) => Read (Required e a) Source # | |
| (Show e, Show a) => Show (Required e a) Source # | |
| Generic (Required e a) Source # | |
| (Monoid e, Eq a) => Semigroup (Required e a) Source # | |
| type Rep (Required e a) Source # | |
Defined in Data.Merge type Rep (Required e a) = D1 ('MetaData "Required" "Data.Merge" "merge-0.3.1.1-9zHUzOVDGVrIUdM92Gcy6Q" 'True) (C1 ('MetaCons "Required" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRequired") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Validation e a)))) | |
Use to get the behavior of
Option (Last a)Last from Data.Monoid
Instances
| Monad Last | Since: base-4.9.0.0 |
| Functor Last | Since: base-4.9.0.0 |
| MonadFix Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Last | Since: base-4.9.0.0 |
| Foldable Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldMap' :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
| Traversable Last | Since: base-4.9.0.0 |
| Bounded a => Bounded (Last a) | Since: base-4.9.0.0 |
| Enum a => Enum (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Eq a => Eq (Last a) | Since: base-4.9.0.0 |
| Data a => Data (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |
| Ord a => Ord (Last a) | Since: base-4.9.0.0 |
| Read a => Read (Last a) | Since: base-4.9.0.0 |
| Show a => Show (Last a) | Since: base-4.9.0.0 |
| Generic (Last a) | Since: base-4.9.0.0 |
| Semigroup (Last a) | Since: base-4.9.0.0 |
| Generic1 Last | Since: base-4.9.0.0 |
| type Rep (Last a) | |
Defined in Data.Semigroup | |
| type Rep1 Last | |
Defined in Data.Semigroup | |
Use to get the behavior of
Option (First a)First from Data.Monoid.
Instances
| Monad First | Since: base-4.9.0.0 |
| Functor First | Since: base-4.9.0.0 |
| MonadFix First | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative First | Since: base-4.9.0.0 |
| Foldable First | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldMap' :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
| Traversable First | Since: base-4.9.0.0 |
| Bounded a => Bounded (First a) | Since: base-4.9.0.0 |
| Enum a => Enum (First a) | Since: base-4.9.0.0 |
| Eq a => Eq (First a) | Since: base-4.9.0.0 |
| Data a => Data (First a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
| Ord a => Ord (First a) | Since: base-4.9.0.0 |
| Read a => Read (First a) | Since: base-4.9.0.0 |
| Show a => Show (First a) | Since: base-4.9.0.0 |
| Generic (First a) | Since: base-4.9.0.0 |
| Semigroup (First a) | Since: base-4.9.0.0 |
| Generic1 First | Since: base-4.9.0.0 |
| type Rep (First a) | |
Defined in Data.Semigroup | |
| type Rep1 First | |
Defined in Data.Semigroup | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
Fields
| |
Instances
| Monad Product | Since: base-4.8.0.0 |
| Functor Product | Since: base-4.8.0.0 |
| Applicative Product | Since: base-4.8.0.0 |
| Foldable Product | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldMap' :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |
| Traversable Product | Since: base-4.8.0.0 |
| Bounded a => Bounded (Product a) | Since: base-2.1 |
| Eq a => Eq (Product a) | Since: base-2.1 |
| Num a => Num (Product a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| Ord a => Ord (Product a) | Since: base-2.1 |
| Read a => Read (Product a) | Since: base-2.1 |
| Show a => Show (Product a) | Since: base-2.1 |
| Generic (Product a) | Since: base-4.7.0.0 |
| Num a => Semigroup (Product a) | Since: base-4.9.0.0 |
| Num a => Monoid (Product a) | Since: base-2.1 |
| Generic1 Product | Since: base-4.7.0.0 |
| type Rep (Product a) | |
Defined in Data.Semigroup.Internal | |
| type Rep1 Product | |
Defined in Data.Semigroup.Internal | |
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
Instances
| Monad Sum | Since: base-4.8.0.0 |
| Functor Sum | Since: base-4.8.0.0 |
| Applicative Sum | Since: base-4.8.0.0 |
| Foldable Sum | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldMap' :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
| Traversable Sum | Since: base-4.8.0.0 |
| Bounded a => Bounded (Sum a) | Since: base-2.1 |
| Eq a => Eq (Sum a) | Since: base-2.1 |
| Num a => Num (Sum a) | Since: base-4.7.0.0 |
| Ord a => Ord (Sum a) | Since: base-2.1 |
| Read a => Read (Sum a) | Since: base-2.1 |
| Show a => Show (Sum a) | Since: base-2.1 |
| Generic (Sum a) | Since: base-4.7.0.0 |
| Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
| Num a => Monoid (Sum a) | Since: base-2.1 |
| Generic1 Sum | Since: base-4.7.0.0 |
| type Rep (Sum a) | |
Defined in Data.Semigroup.Internal | |
| type Rep1 Sum | |
Defined in Data.Semigroup.Internal | |
The dual of a Monoid, obtained by swapping the arguments of mappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
Instances
| Monad Dual | Since: base-4.8.0.0 |
| Functor Dual | Since: base-4.8.0.0 |
| Applicative Dual | Since: base-4.8.0.0 |
| Foldable Dual | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldMap' :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
| Traversable Dual | Since: base-4.8.0.0 |
| Bounded a => Bounded (Dual a) | Since: base-2.1 |
| Eq a => Eq (Dual a) | Since: base-2.1 |
| Ord a => Ord (Dual a) | Since: base-2.1 |
| Read a => Read (Dual a) | Since: base-2.1 |
| Show a => Show (Dual a) | Since: base-2.1 |
| Generic (Dual a) | Since: base-4.7.0.0 |
| Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
| Monoid a => Monoid (Dual a) | Since: base-2.1 |
| Generic1 Dual | Since: base-4.7.0.0 |
| type Rep (Dual a) | |
Defined in Data.Semigroup.Internal | |
| type Rep1 Dual | |
Defined in Data.Semigroup.Internal | |
Instances
| Monad Max | Since: base-4.9.0.0 |
| Functor Max | Since: base-4.9.0.0 |
| MonadFix Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Max | Since: base-4.9.0.0 |
| Foldable Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Max m -> m # foldMap :: Monoid m => (a -> m) -> Max a -> m # foldMap' :: Monoid m => (a -> m) -> Max a -> m # foldr :: (a -> b -> b) -> b -> Max a -> b # foldr' :: (a -> b -> b) -> b -> Max a -> b # foldl :: (b -> a -> b) -> b -> Max a -> b # foldl' :: (b -> a -> b) -> b -> Max a -> b # foldr1 :: (a -> a -> a) -> Max a -> a # foldl1 :: (a -> a -> a) -> Max a -> a # elem :: Eq a => a -> Max a -> Bool # maximum :: Ord a => Max a -> a # | |
| Traversable Max | Since: base-4.9.0.0 |
| Bounded a => Bounded (Max a) | Since: base-4.9.0.0 |
| Enum a => Enum (Max a) | Since: base-4.9.0.0 |
| Eq a => Eq (Max a) | Since: base-4.9.0.0 |
| Data a => Data (Max a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) # dataTypeOf :: Max a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) # gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # | |
| Num a => Num (Max a) | Since: base-4.9.0.0 |
| Ord a => Ord (Max a) | Since: base-4.9.0.0 |
| Read a => Read (Max a) | Since: base-4.9.0.0 |
| Show a => Show (Max a) | Since: base-4.9.0.0 |
| Generic (Max a) | Since: base-4.9.0.0 |
| Ord a => Semigroup (Max a) | Since: base-4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
| Generic1 Max | Since: base-4.9.0.0 |
| type Rep (Max a) | |
Defined in Data.Semigroup | |
| type Rep1 Max | |
Defined in Data.Semigroup | |
Instances
| Monad Min | Since: base-4.9.0.0 |
| Functor Min | Since: base-4.9.0.0 |
| MonadFix Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Min | Since: base-4.9.0.0 |
| Foldable Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Min m -> m # foldMap :: Monoid m => (a -> m) -> Min a -> m # foldMap' :: Monoid m => (a -> m) -> Min a -> m # foldr :: (a -> b -> b) -> b -> Min a -> b # foldr' :: (a -> b -> b) -> b -> Min a -> b # foldl :: (b -> a -> b) -> b -> Min a -> b # foldl' :: (b -> a -> b) -> b -> Min a -> b # foldr1 :: (a -> a -> a) -> Min a -> a # foldl1 :: (a -> a -> a) -> Min a -> a # elem :: Eq a => a -> Min a -> Bool # maximum :: Ord a => Min a -> a # | |
| Traversable Min | Since: base-4.9.0.0 |
| Bounded a => Bounded (Min a) | Since: base-4.9.0.0 |
| Enum a => Enum (Min a) | Since: base-4.9.0.0 |
| Eq a => Eq (Min a) | Since: base-4.9.0.0 |
| Data a => Data (Min a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) # dataTypeOf :: Min a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) # gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # | |
| Num a => Num (Min a) | Since: base-4.9.0.0 |
| Ord a => Ord (Min a) | Since: base-4.9.0.0 |
| Read a => Read (Min a) | Since: base-4.9.0.0 |
| Show a => Show (Min a) | Since: base-4.9.0.0 |
| Generic (Min a) | Since: base-4.9.0.0 |
| Ord a => Semigroup (Min a) | Since: base-4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
| Generic1 Min | Since: base-4.9.0.0 |
| type Rep (Min a) | |
Defined in Data.Semigroup | |
| type Rep1 Min | |
Defined in Data.Semigroup | |