module Util (justWhen,whenNothing,(<.>),deleteByIndices,breakAt ,maybeRead,stripWhitespace) where import Control.Applicative ((<$>)) import Control.Exception (assert) import Data.List (sort) import Data.Char (isSpace) justWhen :: Monad m => Maybe a -> (a -> m ()) -> m () justWhen maybeThis doThis = case maybeThis of Nothing -> return () Just a -> doThis a whenNothing :: Monad m => Maybe a -> m () -> m () whenNothing maybeThis doThis = case maybeThis of Nothing -> doThis _ -> return () (<.>) :: Functor f => (a -> b) -> (c -> f a) -> c -> f b (<.>) p q arg = p <$> (q arg) deleteByIndices :: [Int] -> [a] -> [a] deleteByIndices indices = let deleteByIndex (_,l) ([],list) = ([],l:list) deleteByIndex (lIndex,l) (i:is,list) = if lIndex == i then (is,list) else (i:is,l:list) in assert (indices == (reverse $ sort indices)) . snd . foldr deleteByIndex (indices,[]) . zip [0..] breakAt :: (Eq a) => a -> [a] -> [[a]] breakAt partition list = case dropWhile ((==) partition) list of [] -> [] list' -> element : (breakAt partition list'') where (element,list'') = break ((==) partition) list' maybeRead :: (Read a) => String -> Maybe a maybeRead string = case reads string of [(a,[])] -> Just a _ -> Nothing stripWhitespace :: String -> String stripWhitespace = takeWhile (not . isSpace) . dropWhile isSpace