ghc-6.12.2: The GHC APISource codeContentsIndex
Util
Contents
Flags dependent on the compiler build
General list processing
List operations controlled by another list
For loop
Sorting
Comparisons
Transitive closures
Strictness
Module names
Argument processing
Floating point
IO-ish utilities
Filenames and paths
Description
Highly random utility functions
Synopsis
ghciSupported :: Bool
debugIsOn :: Bool
ghciTablesNextToCode :: Bool
isDynamicGhcLib :: Bool
isWindowsHost :: Bool
isWindowsTarget :: Bool
isDarwinTarget :: Bool
zipEqual :: String -> [a] -> [b] -> [(a, b)]
zipWithEqual :: String -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWith3Equal :: String -> (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith4Equal :: String -> (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
zipLazy :: [a] -> [b] -> [(a, b)]
stretchZipWith :: (a -> Bool) -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
unzipWith :: (a -> b -> c) -> [(a, b)] -> [c]
mapFst :: (a -> c) -> [(a, b)] -> [(c, b)]
mapSnd :: (b -> c) -> [(a, b)] -> [(a, c)]
mapAndUnzip :: (a -> (b, c)) -> [a] -> ([b], [c])
mapAndUnzip3 :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d])
nOfThem :: Int -> a -> [a]
filterOut :: (a -> Bool) -> [a] -> [a]
partitionWith :: (a -> Either b c) -> [a] -> ([b], [c])
splitEithers :: [Either a b] -> ([a], [b])
foldl1' :: (a -> a -> a) -> [a] -> a
foldl2 :: (acc -> a -> b -> acc) -> acc -> [a] -> [b] -> acc
count :: (a -> Bool) -> [a] -> Int
all2 :: (a -> b -> Bool) -> [a] -> [b] -> Bool
lengthExceeds :: [a] -> Int -> Bool
lengthIs :: [a] -> Int -> Bool
lengthAtLeast :: [a] -> Int -> Bool
listLengthCmp :: [a] -> Int -> Ordering
atLength :: ([a] -> b) -> (Int -> b) -> [a] -> Int -> b
equalLength :: [a] -> [b] -> Bool
compareLength :: [a] -> [b] -> Ordering
isSingleton :: [a] -> Bool
only :: [a] -> a
singleton :: a -> [a]
notNull :: [a] -> Bool
snocView :: [a] -> Maybe ([a], a)
isIn :: Eq a => String -> a -> [a] -> Bool
isn'tIn :: Eq a => String -> a -> [a] -> Bool
takeList :: [b] -> [a] -> [a]
dropList :: [b] -> [a] -> [a]
splitAtList :: [b] -> [a] -> ([a], [a])
split :: Char -> String -> [String]
dropTail :: Int -> [a] -> [a]
nTimes :: Int -> (a -> a) -> a -> a
sortLe :: (a -> a -> Bool) -> [a] -> [a]
sortWith :: Ord b => (a -> b) -> [a] -> [a]
on :: (a -> a -> c) -> (b -> a) -> b -> b -> c
isEqual :: Ordering -> Bool
eqListBy :: (a -> a -> Bool) -> [a] -> [a] -> Bool
thenCmp :: Ordering -> Ordering -> Ordering
cmpList :: (a -> a -> Ordering) -> [a] -> [a] -> Ordering
removeSpaces :: String -> String
transitiveClosure :: (a -> [a]) -> (a -> a -> Bool) -> [a] -> [a]
seqList :: [a] -> b -> b
looksLikeModuleName :: String -> Bool
getCmd :: String -> Either String (String, String)
toCmdArgs :: String -> Either String (String, [String])
toArgs :: String -> Either String [String]
readRational :: String -> Rational
createDirectoryHierarchy :: FilePath -> IO ()
doesDirNameExist :: FilePath -> IO Bool
modificationTimeIfExists :: FilePath -> IO (Maybe ClockTime)
global :: a -> IORef a
consIORef :: IORef [a] -> a -> IO ()
globalMVar :: a -> MVar a
globalEmptyMVar :: MVar a
type Suffix = String
splitLongestPrefix :: String -> (Char -> Bool) -> (String, String)
escapeSpaces :: String -> String
parseSearchPath :: String -> [FilePath]
data Direction
= Forwards
| Backwards
reslash :: Direction -> FilePath -> FilePath
Flags dependent on the compiler build
ghciSupported :: BoolSource
debugIsOn :: BoolSource
ghciTablesNextToCode :: BoolSource
isDynamicGhcLib :: BoolSource
isWindowsHost :: BoolSource
isWindowsTarget :: BoolSource
isDarwinTarget :: BoolSource
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
lengthAtLeast :: [a] -> Int -> BoolSource
listLengthCmp :: [a] -> Int -> OrderingSource
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
isSingleton :: [a] -> BoolSource
only :: [a] -> aSource
singleton :: a -> [a]Source
notNull :: [a] -> BoolSource
snocView :: [a] -> Maybe ([a], a)Source
isIn :: Eq a => String -> a -> [a] -> BoolSource
isn'tIn :: Eq a => String -> a -> [a] -> BoolSource
List operations controlled by another list
takeList :: [b] -> [a] -> [a]Source
dropList :: [b] -> [a] -> [a]Source
splitAtList :: [b] -> [a] -> ([a], [a])Source
split :: Char -> String -> [String]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
isEqual :: Ordering -> BoolSource
eqListBy :: (a -> a -> Bool) -> [a] -> [a] -> BoolSource
thenCmp :: Ordering -> Ordering -> OrderingSource
cmpList :: (a -> a -> Ordering) -> [a] -> [a] -> OrderingSource
removeSpaces :: String -> StringSource
Transitive closures
transitiveClosure :: (a -> [a]) -> (a -> a -> Bool) -> [a] -> [a]Source
Strictness
seqList :: [a] -> b -> bSource
Module names
looksLikeModuleName :: String -> BoolSource
Argument processing
getCmd :: String -> Either String (String, String)Source
toCmdArgs :: String -> Either String (String, [String])Source
toArgs :: String -> Either String [String]Source
Floating point
readRational :: String -> RationalSource
IO-ish utilities
createDirectoryHierarchy :: FilePath -> IO ()Source
doesDirNameExist :: FilePath -> IO BoolSource
modificationTimeIfExists :: FilePath -> IO (Maybe ClockTime)Source
global :: a -> IORef aSource
consIORef :: IORef [a] -> a -> IO ()Source
globalMVar :: a -> MVar aSource
globalEmptyMVar :: MVar aSource
Filenames and paths
type Suffix = StringSource
splitLongestPrefix :: String -> (Char -> Bool) -> (String, String)Source
escapeSpaces :: String -> StringSource
parseSearchPath :: String -> [FilePath]Source
The function splits the given string to substrings using the searchPathSeparator.
data Direction Source
Constructors
Forwards
Backwards
reslash :: Direction -> FilePath -> FilePathSource
Produced by Haddock version 2.6.1