module Data.Strict.Either (
Either(..)
, either
, isLeft, isRight
, lefts, rights
, partitionEithers
) where
import qualified Data.Either as L
import Prelude hiding (Either(..), either)
import Data.Bifunctor (Bifunctor(..))
import GHC.Generics (Generic, Generic1)
import Data.Data (Data, Typeable)
import Data.Strict.Class
data Either a b = Left !a | Right !b
deriving (Eq, Ord, Read, Show, Functor, Traversable, Foldable, Generic, Generic1, Data, Typeable)
instance IsStrict (L.Either a b) (Either a b) where
toStrict (L.Left x) = Left x
toStrict (L.Right y) = Right y
fromStrict (Left x) = L.Left x
fromStrict (Right y) = L.Right y
instance Bifunctor Either where
bimap f _ (Left a) = Left (f a)
bimap _ g (Right a) = Right (g a)
first f = either (Left . f) Right
second g = either Left (Right . g)
either :: (a -> c) -> (b -> c) -> Either a b -> c
either f _ (Left x) = f x
either _ g (Right y) = g y
isLeft :: Either a b -> Bool
isLeft (Left _) = True
isLeft _ = False
isRight :: Either a b -> Bool
isRight (Right _) = True
isRight _ = False
lefts :: [Either a b] -> [a]
lefts x = [a | Left a <- x]
rights :: [Either a b] -> [b]
rights x = [a | Right a <- x]
partitionEithers :: [Either a b] -> ([a],[b])
partitionEithers = foldr (either left right) ([], [])
where left a ~(l, r) = (a:l, r)
right a ~(l, r) = (l, a:r)