-- This file is part of htalkat -- Copyright (C) 2021 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module Util where import Control.Monad (unless, when) -- nice tip from one joeyh: whenM,unlessM,(>>?),(>>!) :: Monad m => m Bool -> m () -> m () whenM c a = c >>= flip when a unlessM c a = c >>= flip unless a (>>?) = whenM (>>!) = unlessM -- same precedence as ($), allowing e.g. foo bar >>! error $ "failed " ++ meep infixr 0 >>? infixr 0 >>! maybeToEither :: e -> Maybe a -> Either e a maybeToEither e = maybe (Left e) Right eitherToMaybe :: Either e a -> Maybe a eitherToMaybe (Left _) = Nothing eitherToMaybe (Right a) = Just a