{-# LANGUAGE BangPatterns #-} module RIO.Prelude.Extra ( mapLeft , fromFirst , mapMaybeA , mapMaybeM , forMaybeA , forMaybeM , nubOrd ) where import qualified Data.Set as Set import Data.Monoid (First (..)) import RIO.Prelude.Reexports mapLeft :: (a1 -> a2) -> Either a1 b -> Either a2 b mapLeft f (Left a1) = Left (f a1) mapLeft _ (Right b) = Right b fromFirst :: a -> First a -> a fromFirst x = fromMaybe x . getFirst -- | Applicative 'mapMaybe'. mapMaybeA :: Applicative f => (a -> f (Maybe b)) -> [a] -> f [b] mapMaybeA f = fmap catMaybes . traverse f -- | @'forMaybeA' '==' 'flip' 'mapMaybeA'@ forMaybeA :: Applicative f => [a] -> (a -> f (Maybe b)) -> f [b] forMaybeA = flip mapMaybeA -- | Monadic 'mapMaybe'. mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] mapMaybeM f = liftM catMaybes . mapM f -- | @'forMaybeM' '==' 'flip' 'mapMaybeM'@ forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b] forMaybeM = flip mapMaybeM nubOrd :: Ord a => [a] -> [a] nubOrd = loop mempty where loop _ [] = [] loop !s (a:as) | a `Set.member` s = loop s as | otherwise = a : loop (Set.insert a s) as