ghc-7.8.4: The GHC API

Safe HaskellNone
LanguageHaskell98

Util

Contents

Description

Highly random utility functions

Synopsis

Flags dependent on the compiler build

General list processing

zipEqual :: String -> [a] -> [b] -> [(a, b)] Source

zipWithEqual :: String -> (a -> b -> c) -> [a] -> [b] -> [c] Source

zipWith3Equal :: String -> (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source

zipWith4Equal :: String -> (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] Source

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

zipLazy is a kind of zip that is lazy in the second list (observe the ~)

stretchZipWith :: (a -> Bool) -> b -> (a -> b -> c) -> [a] -> [b] -> [c] Source

stretchZipWith p z f xs ys stretches ys by inserting z in the places where p returns True

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

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

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

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

chkAppend :: [a] -> [a] -> [a] Source

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

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

mapAccumL2 :: (s1 -> s2 -> a -> (s1, s2, b)) -> s1 -> s2 -> [a] -> (s1, s2, [b]) Source

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

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

Like filter, only it reverses the sense of the test

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

Uses a function to determine which of two output lists an input element should join

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

Teases a list of Eithers apart into two lists

foldl1' :: (a -> a -> a) -> [a] -> a Source

A strict version of foldl1

foldl2 :: (acc -> a -> b -> acc) -> acc -> [a] -> [b] -> acc Source

count :: (a -> Bool) -> [a] -> Int Source

all2 :: (a -> b -> Bool) -> [a] -> [b] -> Bool Source

lengthExceeds :: [a] -> Int -> Bool Source

(lengthExceeds xs n) = (length xs > n)

lengthIs :: [a] -> Int -> Bool Source

atLength :: ([a] -> b) -> (Int -> b) -> [a] -> Int -> b Source

atLength atLen atEnd ls n unravels list ls to position n. Precisely:

 atLength atLenPred atEndPred ls n
  | n < 0         = atLenPred n
  | length ls < n = atEndPred (n - length ls)
  | otherwise     = atLenPred (drop n ls)

equalLength :: [a] -> [b] -> Bool Source

compareLength :: [a] -> [b] -> Ordering Source

only :: [a] -> a Source

singleton :: a -> [a] Source

notNull :: [a] -> Bool Source

snocView :: [a] -> Maybe ([a], a) Source

isIn :: Eq a => String -> a -> [a] -> Bool Source

isn'tIn :: Eq a => String -> a -> [a] -> Bool Source

Tuples

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

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

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

firstM :: Monad m => (a -> m c) -> (a, b) -> m (c, b) Source

first3M :: Monad m => (a -> m d) -> (a, b, c) -> m (d, b, c) Source

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

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

List operations controlled by another list

takeList :: [b] -> [a] -> [a] Source

dropList :: [b] -> [a] -> [a] Source

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

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

For loop

nTimes :: Int -> (a -> a) -> a -> a Source

Compose a function with itself n times. (nth rather than twice)

Sorting

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

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

Comparisons

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

eqMaybeBy :: (a -> a -> Bool) -> Maybe a -> Maybe a -> Bool Source

cmpList :: (a -> a -> Ordering) -> [a] -> [a] -> Ordering Source

Edit distance

fuzzyLookup :: String -> [(String, a)] -> [a] Source

Search for possible matches to the users input in the given list, returning a small number of ranked results

Transitive closures

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

Strictness

seqList :: [a] -> b -> b Source

Module names

Argument processing

Floating point

read helpers

IO-ish utilities

global :: a -> IORef a Source

consIORef :: IORef [a] -> a -> IO () Source

Filenames and paths

parseSearchPath :: String -> [FilePath] Source

The function splits the given string to substrings using the searchPathSeparator.

data Direction Source

Constructors

Forwards 
Backwards 

Utils for defining Data instances

mkNoRepType :: String -> DataType Source

Constructs a non-representation for a non-presentable type

Utils for printing C code

Hashing

hashString :: String -> Int32 Source

A sample hash function for Strings. We keep multiplying by the golden ratio and adding. The implementation is:

hashString = foldl' f golden
  where f m c = fromIntegral (ord c) * magic + hashInt32 m
        magic = 0xdeadbeef

Where hashInt32 works just as hashInt shown above.

Knuth argues that repeated multiplication by the golden ratio will minimize gaps in the hash space, and thus it's a good choice for combining together multiple keys to form one.

Here we know that individual characters c are often small, and this produces frequent collisions if we use ord c alone. A particular problem are the shorter low ASCII and ISO-8859-1 character strings. We pre-multiply by a magic twiddle factor to obtain a good distribution. In fact, given the following test:

testp :: Int32 -> Int
testp k = (n - ) . length . group . sort . map hs . take n $ ls
  where ls = [] : [c : l | l <- ls, c <- ['\0'..'\xff']]
        hs = foldl' f golden
        f m c = fromIntegral (ord c) * k + hashInt32 m
        n = 100000

We discover that testp magic = 0.