| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Acme.Functors
Contents
Description
Types are great. Lifting them into some sort of applicative functor makes them even better. This module is an homage to our favorite applicatives, and to the semigroups with which they are instrinsically connected.
- data LiftedButWhy a = LiftedButWhy a
- data OrNot a
- = ActuallyYes a
- | Nope
- data Two a = Two {
- firstOfTwo :: a
- secondOfTwo :: a
- data AnyNumberOf a
- = OneAndMaybeMore a (AnyNumberOf a)
- | ActuallyNone
- (~~) :: a -> AnyNumberOf a -> AnyNumberOf a
- data OneOrMore a = OneOrMore {
- theFirstOfMany :: a
- possiblyMore :: AnyNumberOf a
- data Also extraThing a = Also {
- withoutExtraThing :: a
- theExtraThing :: extraThing
- data OrInstead otherThing a
- = NotInstead a
- | Instead otherThing
- data OrInsteadFirst otherThing a
- = NotInsteadFirst a
- | InsteadFirst otherThing
- data DeterminedBy parameter a = Determination ((->) parameter a)
Lifted-but-why
data LiftedButWhy a Source #
LiftedButWhy is a boring functor that just has one value and no other
structure or interesting properties.
Constructors
| LiftedButWhy a | A value that has been lifted for some damned reason. ... Okay, to be honest, this one is nobody's favorite, but it is included here for completeness. |
Instances
| Monad LiftedButWhy Source # | LiftedButWhy a >>= f = f a |
| Functor LiftedButWhy Source # | |
| Applicative LiftedButWhy Source # | pure = LiftedButWhy LiftedButWhy f <*> LiftedButWhy a = LiftedButWhy (f a) |
| Eq a => Eq (LiftedButWhy a) Source # | |
| Show a => Show (LiftedButWhy a) Source # | |
| Semigroup a => Semigroup (LiftedButWhy a) Source # | LiftedButWhy x <> LiftedButWhy y = LiftedButWhy (x <> y) |
| Monoid a => Monoid (LiftedButWhy a) Source # | mempty = LiftedButWhy mempty |
Or-not
OrNot is somehow slightly more interesting than LiftedButWhy, even
though it may actually contain less. Instead of a value, there might not
be a value.
When you combine stuff with (<*>) or (<>), all of the values need to
be present. If any of them are absent, the whole expression evaluates to
Nope.
Constructors
| ActuallyYes a | Some normal value. |
| Nope | Chuck Testa. |
Instances
| Monad OrNot Source # | |
| Functor OrNot Source # | |
| Applicative OrNot Source # | If you have a function pure = ActuallyYes ActuallyYes f <*> ActuallyYes a = ActuallyYes (f a) _ <*> _ = Nope |
| Eq a => Eq (OrNot a) Source # | |
| Show a => Show (OrNot a) Source # | |
| Semigroup a => Semigroup (OrNot a) Source # | If you have value ActuallyYes a <> ActuallyYes a' = ActuallyYes (a <> a') _ <> _ = Nope |
| Monoid a => Monoid (OrNot a) Source # | mempty = ActuallyYes mempty |
Two
Two is two values. Yep. Just two values.
Constructors
| Two | |
Fields
| |
Instances
| Functor Two Source # | |
| Applicative Two Source # | If you have two functions pure a = Two a a Two f g <*> Two a a' = Two (f a) (g a') |
| Eq a => Eq (Two a) Source # | |
| Show a => Show (Two a) Source # | |
| Semigroup a => Semigroup (Two a) Source # | Two x y <> Two x' y' = Two (x <> x') (y <> y') |
| Monoid a => Monoid (Two a) Source # | mempty = Two mempty mempty |
Any-number-of
data AnyNumberOf a Source #
AnyNumberOf starts to get exciting. Any number of values you want.
Zero... one ... two ... three ... four ... five ... The possibilities are
truly endless.
Constructors
| OneAndMaybeMore a (AnyNumberOf a) | One value, and maybe even more after that! |
| ActuallyNone | Oh. Well this is less fun. |
Instances
| Functor AnyNumberOf Source # | |
| Applicative AnyNumberOf Source # | You can use this to apply any number of functions to any number of arguments. pure a = OneAndMaybeMore a ActuallyNone
OneAndMaybeMore f fs <*> OneAndMaybeMore x xs =
OneAndMaybeMore (f x) (fs <*> xs)
_ <*> _ = ActuallyNoneExample: ( (+ 1) ~~ (* 2) ~~ (+ 5) ~~ ActuallyNone ) <*> ( 1 ~~ 6 ~~ 4 ~~ 37 ~~ ActuallyNone ) = ( 7 ~~ 12 ~~ 9 ~~ ActuallyNone ) This example demonstrates how when there are more arguments than functions,
any excess arguments (in this case, the |
| Eq a => Eq (AnyNumberOf a) Source # | |
| Show a => Show (AnyNumberOf a) Source # | |
| Semigroup a => Semigroup (AnyNumberOf a) Source # | The operation of combining some number of OneAndMaybeMore x xs <> OneAndMaybeMore y ys =
OneAndMaybeMore (x <> y) (xs <> ys)
_ <> _ = ActuallyNone |
| Monoid a => Monoid (AnyNumberOf a) Source # | mempty = mempty ~~ mempty |
(~~) :: a -> AnyNumberOf a -> AnyNumberOf a infixr 5 Source #
Alias for OneAndMaybeMore which provides some brevity.
One-or-more
OneOrMore is more restrictive than AnyNumberOf, yet somehow actually
more interesting, because it excludes that dull situation where there
aren't any values at all.
Constructors
| OneOrMore | |
Fields
| |
Instances
| Functor OneOrMore Source # | |
| Applicative OneOrMore Source # | pure a = OneOrMore a ActuallyNone OneOrMore f fs <*> OneOrMore x xs = OneOrMore (f x) (fs <*> xs) |
| Eq a => Eq (OneOrMore a) Source # | |
| Show a => Show (OneOrMore a) Source # | |
| Semigroup a => Semigroup (OneOrMore a) Source # | OneOrMore a more <> OneOrMore a' more' =
OneOrMore a (more <> OneAndMaybeMore a' more') |
| Monoid a => Monoid (OneOrMore a) Source # | mempty = OneOrMore mempty ActuallyNone |
Also-extra-thing
data Also extraThing a Source #
Also extraThing is a functor in which each value has an extraThing
of some other type that tags along with it.
Constructors
| Also | |
Fields
| |
Instances
| Functor (Also extraThing) Source # | |
| Monoid extraThing => Applicative (Also extraThing) Source # | Dragging the pure = (`Also` mempty)
(f `Also` extra1) <*> (a `Also` extra2) = f a
`Also` (extra1 <> extra2) |
| (Eq extraThing, Eq a) => Eq (Also extraThing a) Source # | |
| (Show extraThing, Show a) => Show (Also extraThing a) Source # | |
| (Semigroup extraThing, Semigroup a) => Semigroup (Also extraThing a) Source # | (a `Also` extra1) <> (a' `Also` extra2) = (a <> a')
`Also` (extra1 <> extra2) |
| (Monoid extraThing, Monoid a) => Monoid (Also extraThing a) Source # | mempty = Also mempty mempty |
Or-instead-other-thing
data OrInstead otherThing a Source #
OrInstead otherThing is a functor in which, instead of having a
value, can actually just have some totally unrelated otherThing instead.
When you combine stuff with (<*>) or (<>), all of the values need to
be present. If any of them are the otherThing instead, then the whole
expression evaluates to the combination of the otherThings.
Constructors
| NotInstead a | Some normal value. |
| Instead otherThing | Some totally unrelated other thing. |
Instances
| Functor (OrInstead otherThing) Source # | |
| Semigroup otherThing => Applicative (OrInstead otherThing) Source # | The possibility of having an pure = NotInstead NotInstead f <*> NotInstead a = NotInstead (f a) Instead other1 <*> Instead other2 = Instead (other1 <> other2) Instead other <*> _ = Instead other _ <*> Instead other = Instead other |
| (Eq otherThing, Eq a) => Eq (OrInstead otherThing a) Source # | |
| (Show otherThing, Show a) => Show (OrInstead otherThing a) Source # | |
| (Semigroup otherThing, Semigroup a) => Semigroup (OrInstead otherThing a) Source # | NotInstead a <> NotInstead a' = NotInstead (a <> a') Instead other1 <> Instead other2 = Instead (other1 <> other2) Instead other <> _ = Instead other _ <> Instead other = Instead other |
| (Semigroup otherThing, Monoid a) => Monoid (OrInstead otherThing a) Source # | |
Or-instead-other-thing ("first" variant)
data OrInsteadFirst otherThing a Source #
OrInsteadFirst otherThing looks a lot like OrInstead otherThing,
but it manages to always be an applicative functor — and even a monad too —
by handling the otherThings a bit more hamfistedly.
When you combine stuff with (<*>) or (<>), all of the values need to
be present. If any of them are the otherThing instead, then the whole
expression evaluates to the first otherThing encountered, ignoring any
additional otherThings that may subsequently pop up
Constructors
| NotInsteadFirst a | Some normal value. |
| InsteadFirst otherThing | Some totally unrelated other thing. |
Instances
| Monad (OrInsteadFirst otherThing) Source # | InsteadFirst other >>= _ = InsteadFirst other NotInsteadFirst a >>= f = f a |
| Functor (OrInsteadFirst otherThing) Source # | |
| Applicative (OrInsteadFirst otherThing) Source # | pure = NotInsteadFirst NotInsteadFirst f <*> NotInsteadFirst a = NotInsteadFirst (f a) InsteadFirst other <*> _ = InsteadFirst other _ <*> InsteadFirst other = InsteadFirst other |
| (Eq otherThing, Eq a) => Eq (OrInsteadFirst otherThing a) Source # | |
| (Show otherThing, Show a) => Show (OrInsteadFirst otherThing a) Source # | |
| (Semigroup otherThing, Semigroup a) => Semigroup (OrInsteadFirst otherThing a) Source # | NotInsteadFirst a <> NotInsteadFirst a' = NotInsteadFirst (a <> a') InsteadFirst other <> _ = InsteadFirst other _ <> InsteadFirst other = InsteadFirst other |
| (Semigroup otherThing, Monoid a) => Monoid (OrInsteadFirst otherThing a) Source # | mempty = NotInsteadFirst mempty |
Determined-by-parameter
data DeterminedBy parameter a Source #
DeterminedBy parameter is a value that... well, we're not really sure
what it is. We'll find out once a parameter is provided.
The mechanism for deciding how the value is determined from the
parameter is opaque; all you can do is test it with different parameters
and see what results. There aren't even Eq or Show instances, which is
annoying.
Constructors
| Determination ((->) parameter a) |
Instances
| Monad (DeterminedBy parameter) Source # | Determination fa >>= ff =
Determination (\x -> let Determination f = ff (fa x) in f x) |
| Functor (DeterminedBy parameter) Source # | |
| Applicative (DeterminedBy parameter) Source # | pure a = Determination (\_ -> a) Determination f <*> Determination a = Determination (\x -> f x (a x)) |
| Semigroup a => Semigroup (DeterminedBy parameter a) Source # | Determination f <> Determination g = Determination (\x -> f x <> g x) |
| Monoid a => Monoid (DeterminedBy parameter a) Source # | mempty = Determination (\_ -> mempty) |