{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Data.Wedge
(
Wedge(..)
, quotWedge
, wedgeLeft
, wedgeRight
, fromWedge
, toWedge
, isHere
, isThere
, isNowhere
, wedge
, heres
, theres
, filterHeres
, filterTheres
, filterNowheres
, foldHeres
, foldTheres
, gatherWedges
, partitionWedges
, mapWedges
, distributeWedge
, codistributeWedge
, reassocLR
, reassocRL
, swapWedge
) where
import Prelude
import Control.Applicative (Alternative (..))
import Control.DeepSeq (NFData (..))
import Data.Bifoldable
import Data.Bifunctor
import Data.Binary (Binary (..))
import Data.Bitraversable
import Data.Data
import Data.Hashable
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup (Semigroup (..))
#endif
import GHC.Generics
data Wedge a b = Nowhere | Here a | There b
deriving
( Eq, Ord, Read, Show
, Generic, Generic1
, Typeable, Data
)
wedge
:: c
-> (a -> c)
-> (b -> c)
-> Wedge a b
-> c
wedge c _ _ Nowhere = c
wedge _ f _ (Here a) = f a
wedge _ _ g (There b) = g b
quotWedge :: Either (Maybe a) (Maybe b) -> Wedge a b
quotWedge (Left a) = maybe Nowhere Here a
quotWedge (Right b) = maybe Nowhere There b
fromWedge :: Wedge a b -> Maybe (Either a b)
fromWedge Nowhere = Nothing
fromWedge (Here a) = Just (Left a)
fromWedge (There b) = Just (Right b)
toWedge :: Maybe (Either a b) -> Wedge a b
toWedge Nothing = Nowhere
toWedge (Just e) = either Here There e
wedgeLeft :: Maybe a -> Wedge a b
wedgeLeft Nothing = Nowhere
wedgeLeft (Just a) = Here a
wedgeRight :: Maybe b -> Wedge a b
wedgeRight Nothing = Nowhere
wedgeRight (Just b) = There b
isHere :: Wedge a b -> Bool
isHere = \case
Here _ -> True
_ -> False
isThere :: Wedge a b -> Bool
isThere = \case
There _ -> True
_ -> False
isNowhere :: Wedge a b -> Bool
isNowhere = \case
Nowhere -> True
_ -> False
heres :: Foldable f => f (Wedge a b) -> [a]
heres = foldr go mempty
where
go (Here a) acc = a:acc
go _ acc = acc
theres :: Foldable f => f (Wedge a b) -> [b]
theres = foldr go mempty
where
go (There b) acc = b:acc
go _ acc = acc
filterHeres :: Foldable f => f (Wedge a b) -> [Wedge a b]
filterHeres = foldr go mempty
where
go (Here _) acc = acc
go ab acc = ab:acc
filterTheres :: Foldable f => f (Wedge a b) -> [Wedge a b]
filterTheres = foldr go mempty
where
go (There _) acc = acc
go ab acc = ab:acc
filterNowheres :: Foldable f => f (Wedge a b) -> [Wedge a b]
filterNowheres = foldr go mempty
where
go Nowhere acc = acc
go ab acc = ab:acc
foldHeres :: Foldable f => (a -> m -> m) -> m -> f (Wedge a b) -> m
foldHeres k = foldr go
where
go (Here a) acc = k a acc
go _ acc = acc
foldTheres :: Foldable f => (b -> m -> m) -> m -> f (Wedge a b) -> m
foldTheres k = foldr go
where
go (There b) acc = k b acc
go _ acc = acc
gatherWedges :: Wedge [a] [b] -> [Wedge a b]
gatherWedges Nowhere = []
gatherWedges (Here as) = fmap Here as
gatherWedges (There bs) = fmap There bs
partitionWedges
:: forall f t a b
. ( Foldable t
, Alternative f
)
=> t (Wedge a b) -> (f a, f b)
partitionWedges = foldr go (empty, empty)
where
go Nowhere acc = acc
go (Here a) (as, bs) = (pure a <|> as, bs)
go (There b) (as, bs) = (as, pure b <|> bs)
mapWedges
:: forall f t a b c
. ( Alternative f
, Traversable t
)
=> (a -> Wedge b c)
-> t a
-> (f b, f c)
mapWedges f = partitionWedges . fmap f
reassocLR :: Wedge (Wedge a b) c -> Wedge a (Wedge b c)
reassocLR = \case
Nowhere -> Nowhere
Here w -> case w of
Nowhere -> There Nowhere
Here a -> Here a
There b -> There (Here b)
There c -> There (There c)
reassocRL :: Wedge a (Wedge b c) -> Wedge (Wedge a b) c
reassocRL = \case
Nowhere -> Nowhere
Here a -> Here (Here a)
There w -> case w of
Nowhere -> Here Nowhere
Here b -> Here (There b)
There c -> There c
distributeWedge :: Wedge (a,b) c -> (Wedge a c, Wedge b c)
distributeWedge = \case
Nowhere -> (Nowhere, Nowhere)
Here (a,b) -> (Here a, Here b)
There c -> (There c, There c)
codistributeWedge :: Either (Wedge a c) (Wedge b c) -> Wedge (Either a b) c
codistributeWedge = \case
Left w -> case w of
Nowhere -> Nowhere
Here a -> Here (Left a)
There c -> There c
Right w -> case w of
Nowhere -> Nowhere
Here b -> Here (Right b)
There c -> There c
swapWedge :: Wedge a b -> Wedge b a
swapWedge = \case
Nowhere -> Nowhere
Here a -> There a
There b -> Here b
instance (Hashable a, Hashable b) => Hashable (Wedge a b)
instance Functor (Wedge a) where
fmap f = \case
Nowhere -> Nowhere
Here a -> Here a
There b -> There (f b)
instance Foldable (Wedge a) where
foldMap f (There b) = f b
foldMap _ _ = mempty
instance Traversable (Wedge a) where
traverse f = \case
Nowhere -> pure Nowhere
Here a -> pure (Here a)
There b -> There <$> f b
instance Semigroup a => Applicative (Wedge a) where
pure = There
_ <*> Nowhere = Nowhere
Nowhere <*> _ = Nowhere
Here a <*> _ = Here a
There _ <*> Here b = Here b
There f <*> There a = There (f a)
instance Semigroup a => Monad (Wedge a) where
return = pure
(>>) = (*>)
Nowhere >>= _ = Nowhere
Here a >>= _ = Here a
There b >>= k = k b
instance (Semigroup a, Semigroup b) => Semigroup (Wedge a b) where
Nowhere <> b = b
a <> Nowhere = a
Here a <> Here b = Here (a <> b)
Here _ <> There b = There b
There a <> Here _ = There a
There a <> There b = There (a <> b)
instance (Semigroup a, Semigroup b) => Monoid (Wedge a b) where
mempty = Nowhere
mappend = (<>)
instance (NFData a, NFData b) => NFData (Wedge a b) where
rnf Nowhere = ()
rnf (Here a) = rnf a
rnf (There b) = rnf b
instance (Binary a, Binary b) => Binary (Wedge a b) where
put Nowhere = put @Int 0
put (Here a) = put @Int 1 >> put a
put (There b) = put @Int 2 >> put b
get = get @Int >>= \case
0 -> pure Nowhere
1 -> Here <$> get
2 -> There <$> get
_ -> fail "Invalid Wedge index"
instance Bifunctor Wedge where
bimap f g = \case
Nowhere -> Nowhere
Here a -> Here (f a)
There b -> There (g b)
instance Bifoldable Wedge where
bifoldMap f g = \case
Nowhere -> mempty
Here a -> f a
There b -> g b
instance Bitraversable Wedge where
bitraverse f g = \case
Nowhere -> pure Nowhere
Here a -> Here <$> f a
There b -> There <$> g b