#if __GLASGOW_HASKELL__ >= 702
#endif
module Data.Witherable
( Filterable(..)
, Witherable(..)
, witherM
, blightM
, ordNub
, hashNub
, forMaybe
, FilterLike, Filter, FilterLike', Filter'
, witherOf
, forMaybeOf
, mapMaybeOf
, catMaybesOf
, filterAOf
, filterOf
, ordNubOf
, hashNubOf
, cloneFilter
, Peat(..)
)
where
import qualified Data.Maybe as Maybe
import qualified Data.IntMap.Lazy as IM
import qualified Data.Map.Lazy as M
import qualified Data.Sequence as S
import qualified Data.Vector as V
import qualified Data.HashMap.Strict as HM
import qualified Data.Set as Set
import qualified Data.HashSet as HSet
import Control.Applicative
import qualified Data.Traversable as T
import qualified Data.Foldable as F
import Data.Functor.Compose
import Data.Hashable
import Data.Functor.Identity
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.State.Strict
import Data.Monoid
import Data.Orphans ()
#if (MIN_VERSION_base(4,7,0))
import Data.Proxy
#endif
import Prelude
type FilterLike f s t a b = (a -> f (Maybe b)) -> s -> f t
type Filter s t a b = forall f. Applicative f => FilterLike f s t a b
type FilterLike' f s a = FilterLike f s s a a
type Filter' s a = forall f. Applicative f => FilterLike' f s a
newtype Peat a b t = Peat { runPeat :: forall f. Applicative f => (a -> f (Maybe b)) -> f t }
instance Functor (Peat a b) where
fmap f (Peat k) = Peat (fmap f . k)
instance Applicative (Peat a b) where
pure a = Peat $ const (pure a)
Peat f <*> Peat g = Peat $ \h -> f h <*> g h
cloneFilter :: FilterLike (Peat a b) s t a b -> Filter s t a b
cloneFilter l f = (`runPeat` f) . l (\a -> Peat $ \g -> g a)
witherOf :: FilterLike f s t a b -> (a -> f (Maybe b)) -> s -> f t
witherOf = id
forMaybeOf :: FilterLike f s t a b -> s -> (a -> f (Maybe b)) -> f t
forMaybeOf = flip
mapMaybeOf :: FilterLike Identity s t a b -> (a -> Maybe b) -> s -> t
mapMaybeOf w f = runIdentity . w (Identity . f)
catMaybesOf :: FilterLike Identity s t (Maybe a) a -> s -> t
catMaybesOf w = mapMaybeOf w id
filterAOf :: Functor f => FilterLike' f s a -> (a -> f Bool) -> s -> f s
filterAOf w f = w $ \a -> (\b -> if b then Just a else Nothing) <$> f a
filterOf :: FilterLike' Identity s a -> (a -> Bool) -> s -> s
filterOf w f = runIdentity . filterAOf w (Identity . f)
class Functor f => Filterable f where
mapMaybe :: (a -> Maybe b) -> f a -> f b
mapMaybe f = catMaybes . fmap f
catMaybes :: f (Maybe a) -> f a
catMaybes = mapMaybe id
filter :: (a -> Bool) -> f a -> f a
filter f = mapMaybe $ \a -> if f a then Just a else Nothing
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 707
#endif
class (T.Traversable t, Filterable t) => Witherable t where
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b)
wither f = fmap catMaybes . T.traverse f
filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a)
filterA = filterAOf wither
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 707
#endif
forMaybe :: (Witherable t, Applicative f) => t a -> (a -> f (Maybe b)) -> f (t b)
forMaybe = flip wither
witherM :: (Witherable t, Monad m) => (a -> MaybeT m b) -> t a -> m (t b)
witherM f = unwrapMonad . wither (WrapMonad . runMaybeT . f)
blightM :: (Monad m, Witherable t) => t a -> (a -> MaybeT m b) -> m (t b)
blightM = flip witherM
ordNubOf :: Ord a => FilterLike' (State (Set.Set a)) s a -> s -> s
ordNubOf w t = evalState (w f t) Set.empty
where
f a = state $ \s -> if Set.member a s
then (Nothing, s)
else (Just a, Set.insert a s)
hashNubOf :: (Eq a, Hashable a) => FilterLike' (State (HSet.HashSet a)) s a -> s -> s
hashNubOf w t = evalState (w f t) HSet.empty
where
f a = state $ \s -> if HSet.member a s
then (Nothing, s)
else (Just a, HSet.insert a s)
ordNub :: (Witherable t, Ord a) => t a -> t a
ordNub = ordNubOf wither
hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a
hashNub = hashNubOf wither
instance Filterable Maybe where
mapMaybe f = (>>= f)
instance Witherable Maybe where
wither _ Nothing = pure Nothing
wither f (Just a) = f a
instance Monoid e => Filterable (Either e) where
mapMaybe _ (Left e) = Left e
mapMaybe f (Right a) = maybe (Left mempty) Right $ f a
instance Monoid e => Witherable (Either e) where
wither _ (Left e) = pure (Left e)
wither f (Right a) = fmap (maybe (Left mempty) Right) (f a)
instance Filterable [] where
mapMaybe = Maybe.mapMaybe
catMaybes = Maybe.catMaybes
filter = Prelude.filter
instance Witherable [] where
wither f = go where
go (x:xs) = maybe id (:) <$> f x <*> go xs
go [] = pure []
instance Filterable IM.IntMap where
mapMaybe = IM.mapMaybe
filter = IM.filter
instance Witherable IM.IntMap where
instance Filterable (M.Map k) where
mapMaybe = M.mapMaybe
filter = M.filter
instance Witherable (M.Map k) where
instance (Eq k, Hashable k) => Filterable (HM.HashMap k) where
mapMaybe = HM.mapMaybe
filter = HM.filter
instance (Eq k, Hashable k) => Witherable (HM.HashMap k) where
#if (MIN_VERSION_base(4,7,0))
instance Filterable Proxy where
mapMaybe _ Proxy = Proxy
instance Witherable Proxy where
wither _ Proxy = pure Proxy
#endif
instance Filterable (Const r) where
mapMaybe _ (Const r) = Const r
instance Witherable (Const r) where
wither _ (Const r) = pure (Const r)
instance Filterable V.Vector where
mapMaybe f = V.fromList . mapMaybe f . V.toList
instance Witherable V.Vector where
wither f = fmap V.fromList . wither f . V.toList
instance Filterable S.Seq where
mapMaybe f = S.fromList . mapMaybe f . F.toList
instance Witherable S.Seq where
wither f = fmap S.fromList . wither f . F.toList
instance (Functor f, Filterable g) => Filterable (Compose f g) where
mapMaybe f = Compose . fmap (mapMaybe f) . getCompose
instance (T.Traversable f, Witherable g) => Witherable (Compose f g) where
wither f = fmap Compose . T.traverse (wither f) . getCompose
instance Functor f => Filterable (MaybeT f) where
mapMaybe f = MaybeT . fmap (mapMaybe f) . runMaybeT
instance (T.Traversable t) => Witherable (MaybeT t) where
wither f = fmap MaybeT . T.traverse (wither f) . runMaybeT