-- | These functions should be built-in haskell... But their not :( -- -- The function type is the documentation for most of these functions module Festung.Utils ( eitherUnitToMaybe , hoistMEither , mapLeft , whenJust , getVersion ) where import Paths_festung (version) import Data.Version (showVersion) import Data.Either (either) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Either (hoistEither, EitherT) import Control.Monad (join) getVersion :: String getVersion = showVersion version eitherUnitToMaybe :: Either () a -> Maybe a eitherUnitToMaybe = either (const Nothing) Just -- | Lift an @'Either' contain in a monad into an @'EitherT' hoistMEither :: Monad m => m (Either e a) -> EitherT e m a hoistMEither meither = join $ lift $ fmap hoistEither meither mapLeft :: (a -> c) -> Either a b -> Either c b mapLeft f = either (Left . f) Right whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) f = f x whenJust Nothing _ = return ()