ajhc-0.8.0.6: Haskell compiler that produce binary through C language

Safe HaskellNone

GenUtil

Contents

Description

This is a collection of random useful utility functions written in pure Haskell 98. In general, it trys to conform to the naming scheme put forth the haskell prelude and fill in the obvious omissions, as well as provide useful routines in general. To ensure maximum portability, no instances are exported so it may be added to any project without conflicts.

Synopsis

Functions

Error reporting

putErr :: String -> IO ()Source

Flushes stdout and writes string to standard error

putErrLn :: String -> IO ()Source

Flush stdout and write string and newline to standard error

putErrDie :: String -> IO aSource

Flush stdout, write string and newline to standard error, then exit program with failure.

Simple deconstruction

fsts :: [(a, b)] -> [a]Source

take the fst of every element of a list

snds :: [(a, b)] -> [b]Source

take the snd of every element of a list

splitEither :: [Either a b] -> ([a], [b])Source

partition a list of eithers.

rights :: [Either a b] -> [b]Source

take just the rights

lefts :: [Either a b] -> [a]Source

take just the lefts

fst3 :: (t, t1, t2) -> tSource

snd3 :: (t, t1, t2) -> t1Source

thd3 :: (t, t1, t2) -> t2Source

System routines

exitSuccess :: IO a

The computation exitSuccess is equivalent to exitWith ExitSuccess, It terminates the program successfully.

exitFailure :: IO a

The computation exitFailure is equivalent to exitWith (ExitFailure exitfail), where exitfail is implementation-dependent.

epoch :: ClockTimeSource

the standard unix epoch

lookupEnv :: Monad m => String -> IO (m String)Source

looks up an enviornment variable and returns it in an arbitrary Monad rather than raising an exception if the variable is not set.

endOfTime :: ClockTimeSource

an arbitrary time in the future

Random routines

repMaybe :: (a -> Maybe a) -> a -> aSource

recursivly apply function to value until it returns Nothing

liftT2 :: (a -> b, c -> d) -> (a, c) -> (b, d)Source

apply functions to values inside a tupele. liftT3 and liftT4 also exist.

liftT3 :: (t -> t3, t1 -> t4, t2 -> t5) -> (t, t1, t2) -> (t3, t4, t5)Source

liftT4 :: (t -> t4, t1 -> t5, t2 -> t6, t3 -> t7) -> (t, t1, t2, t3) -> (t4, t5, t6, t7)Source

snub :: Ord a => [a] -> [a]Source

sorted nub of list, much more efficient than nub, but doesnt preserve ordering.

snubFst :: Ord a => [(a, b)] -> [(a, b)]Source

sorted nub of list of tuples, based solely on the first element of each tuple.

snubUnder :: Ord b => (a -> b) -> [a] -> [a]Source

sorted nub of list based on function of values

smerge :: Ord a => [a] -> [a] -> [a]Source

merge sorted lists in linear time

sortFst :: Ord a => [(a, b)] -> [(a, b)]Source

sort list of tuples, based on first element of each tuple.

groupFst :: Eq a => [(a, b)] -> [[(a, b)]]Source

group list of tuples, based only on equality of the first element of each tuple.

foldl' :: (a -> b -> a) -> a -> [b] -> a

A strict version of foldl.

fmapLeft :: Functor f => (a -> c) -> f (Either a b) -> f (Either c b)Source

fmapRight :: Functor f => (b -> c) -> f (Either a b) -> f (Either a c)Source

isDisjoint :: Eq a => [a] -> [a] -> BoolSource

set operations on lists. (slow!)

isConjoint :: Eq a => [a] -> [a] -> BoolSource

set operations on lists. (slow!)

groupUnder :: Eq b => (a -> b) -> [a] -> [[a]]Source

group a list based on a function of the values.

sortUnder :: Ord b => (a -> b) -> [a] -> [a]Source

sort a list based on a function of the values.

minimumUnder :: Ord b => (a -> b) -> [a] -> aSource

maximumUnder :: Ord b => (a -> b) -> [a] -> aSource

sortGroupUnder :: Ord a => (b -> a) -> [b] -> [[b]]Source

sortGroupUnderF :: Ord a => (b -> a) -> [b] -> [(a, [b])]Source

sortGroupUnderFG :: Ord b => (a -> b) -> (a -> c) -> [a] -> [(b, [c])]Source

sameLength :: [t] -> [t1] -> BoolSource

Monad routines

perhapsM :: Monad m => Bool -> a -> m aSource

repeatM :: Monad m => m a -> m [a]Source

repeatM_ :: Monad m => m a -> m ()Source

replicateM :: Monad m => Int -> m a -> m [a]Source

replicateM_ :: Monad m => Int -> m a -> m ()Source

maybeToMonad :: Monad m => Maybe a -> m aSource

convert a maybe to an arbitrary failable monad

toMonadM :: Monad m => m (Maybe a) -> m aSource

ioM :: Monad m => IO a -> IO (m a)Source

Trasform IO errors into the failing of an arbitrary monad.

ioMp :: MonadPlus m => IO a -> IO (m a)Source

Trasform IO errors into the mzero of an arbitrary member of MonadPlus.

foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m aSource

foldlM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m ()Source

foldl1M :: Monad m => (a -> a -> m a) -> [a] -> m aSource

foldl1M_ :: Monad m => (a -> a -> m a) -> [a] -> m ()Source

maybeM :: Monad m => String -> Maybe a -> m aSource

convert a maybe to an arbitrary failable monad

Text Routines

Quoting

shellQuote :: [String] -> StringSource

quote a set of strings as would be appropriate to pass them as arguments to a sh style shell

simpleQuote :: [String] -> StringSource

quote strings rc style. single quotes protect any characters between them, to get an actual single quote double it up. Inverse of simpleUnquote

Layout

indentLines :: Int -> String -> StringSource

place spaces before each line in string.

trimBlankLines :: String -> StringSource

trim blank lines at beginning and end of string

paragraph :: Int -> String -> StringSource

reformat a string to not be wider than a given width, breaking it up between words.

expandTabs :: String -> StringSource

expand tabs into spaces in a string assuming tabs are every 8 spaces and we are starting at column 0.

Scrambling

Random

intercalate :: [a] -> [[a]] -> [a]

intercalate xs xss is equivalent to (concat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

powerSet :: [a] -> [[a]]Source

compute the power set of a list

randomPermute :: StdGen -> [a] -> [a]Source

randomly permute a list given a RNG

randomPermuteIO :: [a] -> IO [a]Source

randomly permute a list, using the standard random number generator.

chunk :: Int -> [a] -> [[a]]Source

rtup :: t1 -> t -> (t, t1)Source

triple :: t -> t1 -> t2 -> (t, t1, t2)Source

mapFst :: (a -> b) -> (a, c) -> (b, c)Source

mapSnd :: (a -> b) -> (c, a) -> (c, b)Source

mapFsts :: (a -> b) -> [(a, c)] -> [(b, c)]Source

mapSnds :: (a -> b) -> [(c, a)] -> [(c, b)]Source

tr :: String -> String -> String -> StringSource

Translate characters to other characters in a string, if the second argument is empty, delete the characters in the first argument, else map each character to the cooresponding one in the second argument, cycling the second argument if necessary.

overlaps :: Ord a => (a, a) -> (a, a) -> BoolSource

determine if two closed intervals overlap at all.

showDuration :: (Show a, Integral a) => a -> StringSource

translate a number of seconds to a string representing the duration expressed.

readM :: (Monad m, Read a) => String -> m aSource

readsM :: (Monad m, Read a) => String -> m (a, String)Source

split :: (a -> Bool) -> [a] -> [[a]]Source

Splits a list into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg.

 split (=='a') "aabbaca"
 ["", "", "bb", "c", ""]

tokens :: (a -> Bool) -> [a] -> [[a]]Source

Like split, except that sequences of adjacent separators are treated as a single separator. eg.

 tokens (=='a') "aabbaca"
 ["bb","c"]

count :: (a -> Bool) -> [a] -> IntSource

count elements of list that have a given property

hasRepeatUnder :: Ord a1 => (a -> a1) -> [a] -> BoolSource

Option handling

getArgContents :: IO StringSource

behave like while() in perl, go through the argument list, reading the concation of each file name mentioned or stdin if - is on it. If no arguments are given, read stdin.

parseOptSource

Arguments

:: Monad m 
=> String

Argument string, list of valid options with : after ones which accept an argument

-> [String]

Arguments

-> m ([String], [Char], [(Char, String)])

(non-options,flags,options with arguments)

Process options with an option string like the standard C getopt function call.

getOptContents :: String -> IO (String, [Char], [(Char, String)])Source

Combination of parseOpt and getArgContents.

doTime :: String -> IO a -> IO aSource

time task

rspan :: (a -> Bool) -> [a] -> ([a], [a])Source

rbreak :: (a -> Bool) -> [a] -> ([a], [a])Source

rdropWhile :: (a -> Bool) -> [a] -> [a]Source

rtakeWhile :: (a -> Bool) -> [a] -> [a]Source

rbdropWhile :: (a -> Bool) -> [a] -> [a]Source

concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]Source

on :: (a -> a -> b) -> (c -> a) -> c -> c -> bSource

mapMsnd :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)]Source

mapMfst :: Monad m => (b -> m c) -> [(b, a)] -> m [(c, a)]Source

iocatch :: IO a -> (IOException -> IO a) -> IO aSource

catch function only for IOException

Classes

class Monad m => UniqueProducer m whereSource

class for monads which can generate unique values.

Methods

newUniq :: m IntSource

produce a new unique value