module Data.Invertible.Either
( switch
, isLeft
, isRight
, lft
, rgt
, eitherFirst
, eitherSecond
, pivotEither
) where
import Prelude
import Data.Invertible.Bijection
import Data.Invertible.TH
switch :: Either a b <-> Either b a
switch =
[biCase|
Left a <-> Right a
Right a <-> Left a
|]
isLeft :: Either () () <-> Bool
isLeft =
[biCase|
Left () <-> True
Right () <-> False
|]
isRight :: Either () () <-> Bool
isRight =
[biCase|
Right () <-> True
Left () <-> False
|]
lft :: Either a () <-> Maybe a
lft =
[biCase|
Left a <-> Just a
Right () <-> Nothing
|]
rgt :: Either () a <-> Maybe a
rgt =
[biCase|
Left () <-> Nothing
Right a <-> Just a
|]
eitherFirst :: Either (a, c) (b, c) <-> (Either a b, c)
eitherFirst =
[biCase|
Left (a, c) <-> (Left a, c)
Right (b, c) <-> (Right b, c)
|]
eitherSecond :: Either (a, b) (a, c) <-> (a, Either b c)
eitherSecond =
[biCase|
Left (a, b) <-> (a, Left b)
Right (a, c) <-> (a, Right c)
|]
pivotEither :: Either a (Either b c) <-> Either (Either a b) c
pivotEither =
[biCase|
Left a <-> Left (Left a)
Right (Left a) <-> Left (Right a)
Right (Right a) <-> Right a
|]