{- - A collection of utility functions. -} module Hmpf.Util where import System.Random import System.Posix.Time import System.Posix.Types import System.Time import Data.Char ( toLower ) startsWith :: (Eq a) => [a] -> [a] -> Bool _ `startsWith` [] = True [] `startsWith` _ = False (x:xs) `startsWith` (p:prefix) | x == p = xs `startsWith` prefix | otherwise = False time :: IO String time = do t <- (getClockTime >>= toCalendarTime) return . clock $ ( ctMin t + 60 * ctHour t ) {- putStrLn "1 abc 2 def 3 ghi" putStrLn "4 jkl 5 mno 6 pqr" putStrLn "7 stu 8 vwx 9 yz" -} --Converts seconds to min:sec clock :: Int -> String clock secs = min ++ ":" ++ ss where min = show (secs `div` 60) sec = show (secs `mod` 60) zeros = repeat '0' ss = reverse . take 2 . ( ++ zeros ) . reverse $ sec -- eqIgnoreCase :: String -> String -> Bool eqIgnoreCase str1 str2 = let l1 = map toLower str1 l2 = map toLower str2 in l1 == l2 pick :: [a] -> IO a pick lst = do g <- newStdGen let binary = randoms g return . pick' binary $ lst where pick' :: [Bool] -> [a] -> a pick' _ [x] = x pick' (b:bs) xs = case b of True -> pick' bs (left xs) False -> pick' bs (right xs) where n = (length xs) `div` 2 left = take n right = drop n