-- This file is part of Diohsc -- Copyright (C) 2020 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 TupleSections #-} {-# LANGUAGE Safe #-} module Util where import Control.Monad (when, unless) -- 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 >>! -- |Probably I'm missing some nice way to do these with prelude... mapFst :: (a -> c) -> (a,b) -> (c,b) mapFst f (x,y) = (f x,y) mapSnd :: (b -> c) -> (a,b) -> (a,c) mapSnd f (x,y) = (x,f y) mapFstF :: Functor f => (a -> f c) -> (a,b) -> f (c,b) mapFstF f (x,y) = (,y) <$> f x mapSndF :: Functor f => (b -> f c) -> (a,b) -> f (a,c) mapSndF f (x,y) = (x,) <$> f y maybeToEither :: e -> Maybe a -> Either e a maybeToEither e = maybe (Left e) Right