-- (c) 2010 by Daneel S. Yaitskov -- very simple help function module Data.Graph.SimpleUtil where import Monad (liftM) import Data.List import qualified Debug.Trace as T import System.Exit import System.Environment import Text.Regex.Posix ((=~)) map2 :: (a -> b) -> (a,a) -> (b,b) map2 f (a,b) = (f a, f b) -- (length . fromJust) a == (length . fromJust) b -- apa (==) (length . fromJust) a b apa :: (a -> a -> b) -> (c -> a) -> c -> c -> b apa f g a b = f (g a) (g b) -- map first element of a tuple m1of2 f (a,b) = (f a, b) -- map second element of a tuple m2of2 f (a,b) = (a, f b) infix 6 `m1of2` infix 6 `m2of2` takeAfter :: Eq a => a -> [ a ] -> Maybe a takeAfter x l = case dropWhile (x /= ) l of [] -> Nothing l' -> Just $ case tail l' of [] -> head l (a:_) -> a takeBefore :: Eq a => a -> [ a ] -> Maybe a takeBefore _ [] = Nothing takeBefore x l = if x == head l then Just $ last l else case break (x == ) l of (_,[]) -> Nothing (l, _) -> Just $ last l replace :: Eq a => [a] -> [a] -> [a] -> [a] replace a b [] = [] replace a b s@(h:r) = let la = length a in if isPrefixOf a s then b ++ replace a b (drop la s) else h : replace a b r sublist first len lst = take len $ drop first lst (=~+) :: String -> String -> [ String ] (=~+) str pattern = let (_,matched, rest, groups) = str =~ pattern :: (String, String, String, [String]) in groups compareDouble d1 d2 precision = if abs (d1 - d2) < precision then EQ else compare d1 d2 trace :: String -> a -> a trace msg v = T.trace msg v sign x = if abs x < 1e-9 then 0 else x / (abs x)