ghc-7.0.3: The GHC API

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

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

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

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

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

mapAndUnzip3 :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d])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] -> aSource

A strict version of foldl1

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

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

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

lengthExceeds :: [a] -> Int -> BoolSource

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

lengthIs :: [a] -> Int -> BoolSource

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

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] -> BoolSource

compareLength :: [a] -> [b] -> OrderingSource

only :: [a] -> aSource

singleton :: a -> [a]Source

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

isIn :: Eq a => String -> a -> [a] -> BoolSource

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

Tuples

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

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

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

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 -> aSource

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

Sorting

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

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

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

Comparisons

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

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

Edit distance

fuzzyMatch :: String -> [String] -> [String]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 -> bSource

Module names

Argument processing

Floating point

IO-ish utilities

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 -> DataTypeSource

Constructs a non-representation for a non-presentable type