{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE RankNTypes #-}
module Data.Can
(
Can(..)
, canFst
, canSnd
, isOne
, isEno
, isTwo
, isNon
, can
, foldOnes
, foldEnos
, foldTwos
, gatherCans
, ones
, enos
, twos
, filterOnes
, filterEnos
, filterTwos
, filterNons
, canCurry
, canUncurry
, partitionCans
, partitionAll
, partitionEithers
, mapCans
, distributeCan
, codistributeCan
, reassocLR
, reassocRL
, swapCan
) where
import Control.Applicative (Alternative(..))
import Data.Bifunctor
import Data.Bifoldable
import Data.Bitraversable
import Data.Data
import qualified Data.Either as E
import Data.Foldable
import Data.Hashable
import GHC.Generics
data Can a b = Non | One a | Eno b | Two a b
deriving
( Eq, Ord, Read, Show
, Generic, Generic1
, Typeable, Data
)
can
:: c
-> (a -> c)
-> (b -> c)
-> (a -> b -> c)
-> Can a b
-> c
can c _ _ _ Non = c
can _ f _ _ (One a) = f a
can _ _ g _ (Eno b) = g b
can _ _ _ h (Two a b) = h a b
canFst :: Can a b -> Maybe a
canFst = \case
One a -> Just a
Two a _ -> Just a
_ -> Nothing
canSnd :: Can a b -> Maybe b
canSnd = \case
Eno b -> Just b
Two _ b -> Just b
_ -> Nothing
isOne :: Can a b -> Bool
isOne (One _) = True
isOne _ = False
isEno :: Can a b -> Bool
isEno (Eno _) = True
isEno _ = False
isTwo :: Can a b -> Bool
isTwo (Two _ _) = True
isTwo _ = False
isNon :: Can a b -> Bool
isNon Non = True
isNon _ = False
ones :: Foldable f => f (Can a b) -> [a]
ones = foldr go []
where
go (One a) acc = a:acc
go _ acc = acc
enos :: Foldable f => f (Can a b) -> [b]
enos = foldr go []
where
go (Eno a) acc = a:acc
go _ acc = acc
twos :: Foldable f => f (Can a b) -> [(a,b)]
twos = foldr go []
where
go (Two a b) acc = (a,b):acc
go _ acc = acc
filterOnes :: Foldable f => f (Can a b) -> [Can a b]
filterOnes = foldr go []
where
go (One _) acc = acc
go t acc = t:acc
filterEnos :: Foldable f => f (Can a b) -> [Can a b]
filterEnos = foldr go []
where
go (Eno _) acc = acc
go t acc = t:acc
filterTwos :: Foldable f => f (Can a b) -> [Can a b]
filterTwos = foldr go []
where
go (Two _ _) acc = acc
go t acc = t:acc
filterNons :: Foldable f => f (Can a b) -> [Can a b]
filterNons = foldr go []
where
go Non acc = acc
go t acc = t:acc
foldOnes :: Foldable f => (a -> m -> m) -> m -> f (Can a b) -> m
foldOnes k = foldr go
where
go (One a) acc = k a acc
go _ acc = acc
foldEnos :: Foldable f => (b -> m -> m) -> m -> f (Can a b) -> m
foldEnos k = foldr go
where
go (Eno b) acc = k b acc
go _ acc = acc
foldTwos :: Foldable f => (a -> b -> m -> m) -> m -> f (Can a b) -> m
foldTwos k = foldr go
where
go (Two a b) acc = k a b acc
go _ acc = acc
gatherCans :: Can [a] [b] -> [Can a b]
gatherCans Non = []
gatherCans (One as) = fmap One as
gatherCans (Eno bs) = fmap Eno bs
gatherCans (Two as bs) = zipWith Two as bs
partitionAll :: Foldable f => f (Can a b) -> ([a], [b], [(a,b)])
partitionAll = flip foldr mempty $ \aa ~(as, bs, cs) -> case aa of
Non -> (as, bs, cs)
One a -> (a:as, bs, cs)
Eno b -> (as, b:bs, cs)
Two a b -> (as, bs, (a,b):cs)
partitionEithers :: Foldable f => f (Either a b) -> Can [a] [b]
partitionEithers = go . E.partitionEithers . toList
where
go ([], []) = Non
go (ls, []) = One ls
go ([], rs) = Eno rs
go (ls, rs) = Two ls rs
partitionCans
:: forall f t a b
. ( Foldable t
, Alternative f
)
=> t (Can a b) -> (f a, f b)
partitionCans = foldr go (empty, empty)
where
go Non acc = acc
go (One a) (as, bs) = (pure a <|> as, bs)
go (Eno b) (as, bs) = (as, pure b <|> bs)
go (Two a b) (as, bs) = (pure a <|> as, pure b <|> bs)
mapCans
:: forall f t a b c
. ( Alternative f
, Traversable t
)
=> (a -> Can b c)
-> t a
-> (f b, f c)
mapCans f = partitionCans . fmap f
distributeCan :: Can (a,b) c -> (Can a c, Can b c)
distributeCan = \case
Non -> (Non, Non)
One (a,b) -> (One a, One b)
Eno c -> (Eno c, Eno c)
Two (a,b) c -> (Two a c, Two b c)
codistributeCan :: Either (Can a c) (Can b c) -> Can (Either a b) c
codistributeCan = \case
Left ac -> case ac of
Non -> Non
One a -> One (Left a)
Eno c -> Eno c
Two a c -> Two (Left a) c
Right bc -> case bc of
Non -> Non
One b -> One (Right b)
Eno c -> Eno c
Two b c -> Two (Right b) c
reassocLR :: Can (Can a b) c -> Can a (Can b c)
reassocLR = \case
Non -> Non
One c -> case c of
Non -> Eno Non
One a -> One a
Eno b -> Eno (One b)
Two a b -> Two a (One b)
Eno c -> Eno (Eno c)
Two c d -> case c of
Non -> Eno (Eno d)
One a -> Two a (Eno d)
Eno b -> Eno (Two b d)
Two a b -> Two a (Two b d)
reassocRL :: Can a (Can b c) -> Can (Can a b) c
reassocRL = \case
Non -> Non
One a -> One (One a)
Eno c -> case c of
Non -> One Non
One b -> One (Eno b)
Eno d -> Eno d
Two b d -> Two (Eno b) d
Two a c -> case c of
Non -> One (One a)
One b -> One (Two a b)
Eno d -> Two (One a) d
Two b d -> Two (Two a b) d
swapCan :: Can a b -> Can b a
swapCan = \case
Non -> Non
One a -> Eno a
Eno b -> One b
Two a b -> Two b a
canCurry :: (Can a b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c
canCurry k ma mb = case (ma, mb) of
(Nothing, Nothing) -> k Non
(Just a, Nothing) -> k (One a)
(Nothing, Just b) -> k (Eno b)
(Just a, Just b) -> k (Two a b)
canUncurry :: (Maybe a -> Maybe b -> Maybe c) -> Can a b -> Maybe c
canUncurry k = \case
Non -> k Nothing Nothing
One a -> k (Just a) Nothing
Eno b -> k Nothing (Just b)
Two a b -> k (Just a) (Just b)
instance (Hashable a, Hashable b) => Hashable (Can a b)
instance Functor (Can a) where
fmap _ Non = Non
fmap _ (One a) = One a
fmap f (Eno b) = Eno (f b)
fmap f (Two a b) = Two a (f b)
instance Foldable (Can a) where
foldMap k (Eno b) = k b
foldMap k (Two _ b) = k b
foldMap _ _ = mempty
instance Traversable (Can a) where
traverse k = \case
Non -> pure Non
One a -> pure (One a)
Eno b -> Eno <$> k b
Two a b -> Two a <$> k b
instance Semigroup a => Applicative (Can a) where
pure = Eno
_ <*> Non = Non
Non <*> _ = Non
One a <*> _ = One a
Eno _ <*> One b = One b
Eno f <*> Eno a = Eno (f a)
Eno f <*> Two a b = Two a (f b)
Two a _ <*> One b = One (a <> b)
Two a f <*> Eno b = Two a (f b)
Two a f <*> Two b c = Two (a <> b) (f c)
instance Semigroup a => Monad (Can a) where
return = pure
(>>) = (*>)
Non >>= _ = Non
One a >>= _ = One a
Eno b >>= k = k b
Two a b >>= k = case k b of
Non -> Non
One c -> One (a <> c)
Eno c -> Eno c
Two c d -> Two (a <> c) d
instance (Semigroup a, Semigroup b) => Semigroup (Can a b) where
Non <> b = b
b <> Non = b
One a <> One b = One (a <> b)
One a <> Eno b = Two a b
One a <> Two b c = Two (a <> b) c
Eno a <> Eno b = Eno (a <> b)
Eno b <> One a = Two a b
Eno b <> Two a c = Two a (b <> c)
Two a b <> Two c d = Two (a <> c) (b <> d)
Two a b <> One c = Two (a <> c) b
Two a b <> Eno c = Two a (b <> c)
instance (Semigroup a, Semigroup b) => Monoid (Can a b) where
mempty = Non
instance Bifunctor Can where
bimap f g = \case
Non -> Non
One a -> One (f a)
Eno b -> Eno (g b)
Two a b -> Two (f a) (g b)
instance Bifoldable Can where
bifoldMap f g = \case
Non -> mempty
One a -> f a
Eno b -> g b
Two a b -> f a <> g b
instance Bitraversable Can where
bitraverse f g = \case
Non -> pure Non
One a -> One <$> f a
Eno b -> Eno <$> g b
Two a b -> Two <$> f a <*> g b