sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Util
Synopsis
data SuccFail a
= Succ a
| Fail String
parsef :: Read a => String -> String -> String -> SuccFail a
parseInt :: String -> String -> SuccFail Int
parseDouble :: String -> String -> SuccFail Double
parseVerbatim :: String -> String -> SuccFail String
par :: String -> [String] -> String
putCatsLn :: [String] -> IO ()
putCatLn :: [String] -> IO ()
info :: Show t => t -> IO ()
fake :: String -> IO ()
stub :: String -> IO ()
errcat :: [String] -> a
errcats :: [String] -> a
map2 :: (a -> b) -> [[a]] -> [[b]]
mapM2 :: Monad m => (a -> m b) -> [[a]] -> m [[b]]
adjustAList :: Eq k => k -> (v -> v) -> [(k, v)] -> [(k, v)]
adjustAListM :: (Eq k, Monad m) => k -> (v -> m v) -> [(k, v)] -> m [(k, v)]
insertLastLast :: [[a]] -> a -> [[a]]
insertLast :: [a] -> a -> [a]
Documentation
Parser Utilities
data SuccFail a Source
Constructors
Succ a
Fail String
show/hide Instances
parsef :: Read a => String -> String -> String -> SuccFail aSource
parseInt :: String -> String -> SuccFail IntSource
parseDouble :: String -> String -> SuccFail DoubleSource
parseVerbatim :: String -> String -> SuccFail StringSource
String Utilities
par :: String -> [String] -> StringSource
Enclose in parentheses, like a Lisp function call. Example: par foo [x, y] = (foo x y)
putCatsLn :: [String] -> IO ()Source
Write a list of words, separated by spaces
putCatLn :: [String] -> IO ()Source
Write a list of words, not separated by spaces
info :: Show t => t -> IO ()Source
fake :: String -> IO ()Source
stub :: String -> IO ()Source
Error Reporting
errcat :: [String] -> aSource
Signal an error using a list of strings to be concatenated
errcats :: [String] -> aSource
Signal an error using a list of strings to be concatenated with spaces between (unwords).
List Utilities
map2 :: (a -> b) -> [[a]] -> [[b]]Source
Generalization of map to lists of lists
mapM2 :: Monad m => (a -> m b) -> [[a]] -> m [[b]]Source
Generalization of mapM to lists of lists
adjustAList :: Eq k => k -> (v -> v) -> [(k, v)] -> [(k, v)]Source
Update a value at a given key by applying a function. Similar to Data.Map.adjust.
adjustAListM :: (Eq k, Monad m) => k -> (v -> m v) -> [(k, v)] -> m [(k, v)]Source
Monadic generalization of adjustAList
insertLastLast :: [[a]] -> a -> [[a]]Source
Insert an item into a list of lists of items, making it the last element in the last sublist
insertLast :: [a] -> a -> [a]Source
Insert an item in a list of items, making it the last element
Produced by Haddock version 2.6.1