module Language.CalDims.Helpers ( F , headWithDefault , again , third , unlines' , logBaseInt , (#&&#) , combination , permutation , if_ -- functional if , ErrorAndState , eqClassesWith ) where import Control.Monad.Error import Control.Monad.State type ErrorAndState e s a = ErrorT e (State s) a type F = Double unlines' :: [String] -> String unlines' [] = "" unlines' [a] = a unlines' (a:as) = a ++ "\n" ++ unlines' as logBaseInt :: Integral a => a -> a -> Maybe a logBaseInt a b = if a ^ res == b then Just res else Nothing where res = round (logBase (fromIntegral a) (fromIntegral b) :: Double) again :: Monad m => (a -> m b) -> [a] -> m () again _ [] = return () again f (x:xs) = f x >> again f xs headWithDefault :: a -> [a] -> a headWithDefault a [] = a headWithDefault _ (a:_) = a (#&&#) :: Monad m => m Bool -> m Bool -> m Bool (#&&#) = liftM2 (&&) third :: (a, b, c) -> c third (_, _, c) = c --tc :: Eq a => (a -> [a]) -> a -> [a] --tc f start = start : concatMap (tc f) (filter (/= start) $ f start) if_ :: Bool -> a -> a -> a if_ True a _ = a if_ False _ b = b eqClassesWith :: (a -> a -> Bool) -> [a] -> [(a,[a])] eqClassesWith f l = foldl (ff f) [] l ff :: (a -> a -> Bool) -> [(a, [a])] -> a -> [(a, [a])] ff _ [] a = [(a, [])] ff f ((r,rs):on) a = if f r a then ((r,(a:rs)):on) else (r,rs):(ff f on a) -- combination i l lists all combinations (without repetitions) of set l of order i -- example: -- ["abc","abd","acd","bcd"] combination :: Int -> [a] -> [[a]] combination i l | i > length l = error "i > len l" | i == 1 = map (\x -> [x]) l | null l = [] | i == length l = [l] | otherwise = let (a:as) = l in zipWith (:) (repeat a) (combination (i - 1) as) ++ combination i as permutation :: Int -> [a] -> [[a]] permutation i l | i < 1 = error "i > len l" | i == 1 = map (\x -> [x]) l | otherwise = [ x:y | x <- l, y <- (permutation (i - 1) l)]