{-# LANGUAGE FlexibleInstances,FlexibleContexts,FunctionalDependencies #-} module Utils2(module Utils2,(<>),mconcat) where import qualified Prelude as P import Prelude hiding (splitAt,replicate,zipWith) import Data.Monoid(Monoid(..),(<>)) import Data.Char import Data.List(sort) pair x y = (x,y) mapPair (f,g) (x,y) = (f x,g y) mapFst = map . apFst mapSnd = map . apSnd apFst f (x,y) = (f x,y) apSnd f (x,y) = (x,f y) aboth f (x,y) = (f x,f y) swap (x,y) = (y,x) pairwith f x = (x,f x) dup x = (x,x) oo f g x y = f (g x y) eqBy f x y = f x==f y space n = if n<0 then error "Utils2.space: negative argument" else P.replicate n ' ' words' cs = case break isSpace cs of ([],[]) -> [] ([],cs2) -> words'' cs2 (cs1,cs2) -> cs1:words'' cs2 words'' cs = case span isSpace cs of ([],[]) -> [] ([],cs2) -> words' cs2 (cs1,cs2) -> cs1:words' cs2 trim = reverse.trim1.reverse.trim1 where trim1 = dropWhile isSpace unquote s@('"':r@(_:_)) = if last r == '"' then init r else s unquote s = s expandtabs n = exp n where exp k [] = [] exp k ('\t':xs) = space k ++ exp n xs exp k (x:xs) = x:exp (if k==1 then n else k-1) xs mix :: [[a]] -> [a] -> [a] mix [] d = [] mix (x:xs) d = x++case xs of [] -> []; _ -> d ++ mix xs d strToLower, strToUpper :: String -> String strToLower = map toLower strToUpper = map toUpper addcr "" = "" addcr ('\n':s) = '\r':'\n':addcr s addcr (c:s) = c:addcr s crlf="\r\n" unmix sep xs = case break (sep==) xs of ([],[]) -> [] (xs,[]) -> [xs] (xs,[sep]) -> [xs,[]] (xs,sep:ys) -> xs:unmix sep ys bits :: Integral a => Int->Int->a->a bits p s n = n `quot` (2^p) `rem` 2^s bit p n = bits p 1 n /= 0 mynub xs = nubit.sort.nubit $ xs where nubit [] = [] nubit (x:y:xs) | x == y = nubit (y:xs) nubit (x:xs) = x : nubit xs isSpace' c = c/='\xa0' && isSpace c -- | If 'ReadS' wasn't a type synonym: -- @instance Functor ReadS where fmap = mapR@ mapR f rs = [(f x,r)|(x,r)<-rs] -- ** From hbc-library ListUtil: -- | Repeatedly extract (and transform) values until a predicate hold. -- Return the list of values. unfoldr :: (a -> (b, a)) -> (a -> Bool) -> a -> [b] unfoldr f p x | p x = [] | otherwise = case f x of (y, x') -> y:unfoldr f p x' --chopList :: ([a] -> (b, [a])) -> [a] -> [b] chopList f l = unfoldr f isEmpty l breakAt :: (Eq a) => a -> [a] -> ([a], [a]) breakAt _ [] = ([], []) breakAt x (x':xs) = if x == x' then ([], xs) else let (ys, zs) = breakAt x xs in (x':ys, zs) pieces n = chopList (splitAt n) class Monoid bs => Split bs where isEmpty :: bs -> Bool splitAt :: Int -> bs -> (bs,bs) class Split bs => Zip b bs | bs->b where single :: b -> bs replicate :: Int -> b -> bs zipWith :: (b->b->b) -> bs -> bs -> bs single = replicate 1 instance Split [a] where isEmpty = null splitAt = P.splitAt instance Zip a [a] where single x = [x] replicate = P.replicate zipWith = P.zipWith -- * Re-exports