module Data.Enumerator.Util where import Data.Enumerator import qualified Control.Exception as E tryStep :: IO t -> (t -> IO (Step E.SomeException a IO b)) -> IO (Step E.SomeException a IO b) tryStep get io = do tried <- E.try get case tried of Right t -> io t Left err -> return $ Error err {-# INLINE tryStep #-} mapEither :: (a -> Either e b) -> [a] -> Either e [b] mapEither f = loop [] where loop acc [] = Right (reverse acc) loop acc (a:as) = case f a of Left err -> Left err Right b -> loop (b:acc) as {-# INLINE mapEither #-}