{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} module ControlMaybe ( module ControlMaybe , module Data.Functor ) where -- import GHC.IO.Exception (IOException(..)) import Control.Monad import Data.Functor import System.IO.Error -- forM_ with less polymorphism. withJust :: Monad m => Maybe x -> (x -> m ()) -> m () withJust m f = forM_ m f {-# INLINE withJust #-} whenJust :: Monad m => m (Maybe x) -> (x -> m ()) -> m () whenJust acn f = acn >>= mapM_ f {-# INLINE whenJust #-} catchIO_ :: IO a -> IO a -> IO a catchIO_ body catcher = catchIOError body (\_ -> catcher) {-# INLINE catchIO_ #-} handleIO_ :: IO a -> IO a -> IO a handleIO_ catcher body = catchIOError body (\_ -> catcher) {-# INLINE handleIO_ #-} handleIO :: (IOError -> IO a) -> IO a -> IO a handleIO catcher body = catchIOError body catcher {-# INLINE handleIO #-} #if !MIN_VERSION_base(4,11,0) -- | Flipped version of '<$>'. -- -- @ -- ('<&>') = 'flip' 'fmap' -- @ -- -- @since 4.11.0.0 -- -- ==== __Examples__ -- Apply @(+1)@ to a list, a 'Data.Maybe.Just' and a 'Data.Either.Right': -- -- >>> Just 2 <&> (+1) -- Just 3 -- -- >>> [1,2,3] <&> (+1) -- [2,3,4] -- -- >>> Right 3 <&> (+1) -- Right 4 -- (<&>) :: Functor f => f a -> (a -> b) -> f b as <&> f = f <$> as infixl 1 <&> #endif