{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE InstanceSigs #-}
module Refined.These
(
These(This, That, These)
, these
, fromThese
, mergeThese
, mergeTheseWith
, here, there
, justThis
, justThat
, justThese
, catThis
, catThat
, catThese
, partitionThese
, isThis
, isThat
, isThese
, mapThese
, mapThis
, mapThat
) where
import Control.DeepSeq (NFData(rnf))
#if MIN_VERSION_base(4,10,0)
import Data.Bifoldable (Bifoldable(bifold, bifoldr, bifoldl))
#endif
#if MIN_VERSION_base(4,8,0)
import Data.Bifunctor (Bifunctor(bimap, first, second))
#endif
import Data.Data (Data)
import Data.Maybe (isJust, mapMaybe)
import Data.Semigroup (Semigroup((<>)))
import Data.Typeable (Typeable)
import GHC.Generics (Generic, Generic1)
data These a b = This a | That b | These a b
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic, Generic1)
these :: (a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c
these l _ _ (This a) = l a
these _ r _ (That x) = r x
these _ _ lr (These a x) = lr a x
fromThese :: a -> b -> These a b -> (a, b)
fromThese _ x (This a ) = (a, x)
fromThese a _ (That x ) = (a, x)
fromThese _ _ (These a x) = (a, x)
mergeThese :: (a -> a -> a) -> These a a -> a
mergeThese = these id id
mergeTheseWith :: (a -> c) -> (b -> c) -> (c -> c -> c) -> These a b -> c
mergeTheseWith f g op t = mergeThese op $ mapThese f g t
here :: (Applicative f) => (a -> f b) -> These a t -> f (These b t)
here f (This x) = This <$> f x
here f (These x y) = flip These y <$> f x
here _ (That x) = pure (That x)
there :: (Applicative f) => (a -> f b) -> These t a -> f (These t b)
there _ (This x) = pure (This x)
there f (These x y) = These x <$> f y
there f (That x) = That <$> f x
justThis :: These a b -> Maybe a
justThis = these Just (\_ -> Nothing) (\_ _ -> Nothing)
justThat :: These a b -> Maybe b
justThat = these (\_ -> Nothing) Just (\_ _ -> Nothing)
justThese :: These a b -> Maybe (a, b)
justThese = these (\_ -> Nothing) (\_ -> Nothing) (\a b -> Just (a, b))
isThis, isThat, isThese :: These a b -> Bool
isThis = isJust . justThis
isThat = isJust . justThat
isThese = isJust . justThese
mapThese :: (a -> c) -> (b -> d) -> These a b -> These c d
mapThese f _ (This a ) = This (f a)
mapThese _ g (That x) = That (g x)
mapThese f g (These a x) = These (f a) (g x)
mapThis :: (a -> c) -> These a b -> These c b
mapThis f = mapThese f id
mapThat :: (b -> d) -> These a b -> These a d
mapThat f = mapThese id f
catThis :: [These a b] -> [a]
catThis = mapMaybe justThis
catThat :: [These a b] -> [b]
catThat = mapMaybe justThat
catThese :: [These a b] -> [(a, b)]
catThese = mapMaybe justThese
partitionThese :: [These a b] -> ( [(a, b)], ([a], [b]) )
partitionThese [] = ([], ([], []))
partitionThese (These x y:xs) = first ((x, y):) $ partitionThese xs
partitionThese (This x :xs) = second (first (x:)) $ partitionThese xs
partitionThese (That y:xs) = second (second (y:)) $ partitionThese xs
instance (Semigroup a, Semigroup b) => Semigroup (These a b) where
This a <> This b = This (a <> b)
This a <> That y = These a y
This a <> These b y = These (a <> b) y
That x <> This b = These b x
That x <> That y = That (x <> y)
That x <> These b y = These b (x <> y)
These a x <> This b = These (a <> b) x
These a x <> That y = These a (x <> y)
These a x <> These b y = These (a <> b) (x <> y)
#if MIN_VERSION_base(4,8,0)
instance Bifunctor These where
bimap :: (a -> c) -> (b -> d) -> These a b -> These c d
bimap f _ (This a ) = This (f a)
bimap _ g (That b) = That (g b)
bimap f g (These a b) = These (f a) (g b)
first :: (a -> c) -> These a b -> These c b
first f = bimap f id
second :: (b -> d) -> These a b -> These a d
second f = bimap id f
#endif
instance Functor (These a) where
fmap _ (This x) = This x
fmap f (That y) = That (f y)
fmap f (These x y) = These x (f y)
instance Semigroup a => Applicative (These a) where
pure = That
This a <*> _ = This a
That _ <*> This b = This b
That f <*> That x = That (f x)
That f <*> These b x = These b (f x)
These a _ <*> This b = This (a <> b)
These a f <*> That x = These a (f x)
These a f <*> These b x = These (a <> b) (f x)
instance Semigroup a => Monad (These a) where
return = pure
This a >>= _ = This a
That x >>= k = k x
These a x >>= k = case k x of
This b -> This (a <> b)
That y -> These a y
These b y -> These (a <> b) y
instance (NFData a, NFData b) => NFData (These a b) where
rnf (This a) = rnf a
rnf (That b) = rnf b
rnf (These a b) = rnf a `seq` rnf b
instance Foldable (These a) where
foldr _ z (This _) = z
foldr f z (That x) = f x z
foldr f z (These _ x) = f x z
instance Traversable (These a) where
traverse _ (This a ) = pure $ This a
traverse f (That x) = That <$> f x
traverse f (These a x) = These a <$> f x
sequenceA (This a ) = pure $ This a
sequenceA (That x) = That <$> x
sequenceA (These a x) = These a <$> x
#if MIN_VERSION_base(4,10,0)
instance Bifoldable These where
bifold = these id id mappend
bifoldr f g z = these (`f` z) (`g` z) (\x y -> x `f` (y `g` z))
bifoldl f g z = these (z `f`) (z `g`) (\x y -> (z `f` x) `g` y)
#endif