Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Extensions |
|
Either Projections, inspired by Scala's Either.
Example:
>>>
let process = (+) 100 . (4 *)
>>>
let foo = fmap (10 *) . rightProjection
>>>
let ok = Right 10 :: Either String Int
>>>
let fail = Left "wrong input" :: Either String Int
>>>
foo ok
RightProjection 140
>>>
foo fail
RightNothing "wrong input"
>>>
toMaybe $ foo fail
Nothing
>>>
toMaybe $ foo ok
Just 140
>>>
toEither $ foo fail
Left "wrong input"
>>>
mergeEither . toEither . fmap show $ rightProjection ok
"10"
- class EitherProjection proj left right side | proj -> left, proj -> right, proj -> side where
- type LeftProjection l r = LeftProjection' r l
- data LeftProjection' r l
- data RightProjection l r
- leftProjection :: Either l r -> LeftProjection l r
- rightProjection :: Either l r -> RightProjection l r
- mergeEither :: Either a a -> a
Projections.
class EitherProjection proj left right side | proj -> left, proj -> right, proj -> side where Source
A projection of Either
.
EitherProjection (RightProjection l r) l r r Source | |
EitherProjection (LeftProjection l r) l r l Source |
type LeftProjection l r = LeftProjection' r l Source
Left
projection.
data LeftProjection' r l Source
Functor (LeftProjection' r) Source | |
(Eq r, Eq l) => Eq (LeftProjection' r l) Source | |
(Ord r, Ord l) => Ord (LeftProjection' r l) Source | |
(Read r, Read l) => Read (LeftProjection' r l) Source | |
(Show r, Show l) => Show (LeftProjection' r l) Source | |
EitherProjection (LeftProjection l r) l r l Source |
data RightProjection l r Source
Right
projection.
Functor (RightProjection l) Source | |
(Eq l, Eq r) => Eq (RightProjection l r) Source | |
(Ord l, Ord r) => Ord (RightProjection l r) Source | |
(Read l, Read r) => Read (RightProjection l r) Source | |
(Show l, Show r) => Show (RightProjection l r) Source | |
EitherProjection (RightProjection l r) l r r Source |
leftProjection :: Either l r -> LeftProjection l r Source
Get left projection.
rightProjection :: Either l r -> RightProjection l r Source
Get right projection.