Safe Haskell | None |
---|---|
Language | Haskell2010 |
Standard imports and utilities which are useful everywhere, or needed low in the module hierarchy. This is the bottom of hledger's module graph.
- lowercase :: [Char] -> [Char]
- uppercase :: [Char] -> [Char]
- strip :: [Char] -> String
- lstrip :: String -> String
- rstrip :: [Char] -> [Char]
- stripbrackets :: String -> String
- elideLeft :: Int -> [Char] -> [Char]
- elideRight :: Int -> [Char] -> [Char]
- underline :: String -> String
- quoteIfSpaced :: String -> String
- quoteIfNeeded :: [Char] -> [Char]
- singleQuoteIfNeeded :: [Char] -> [Char]
- quotechars :: [Char]
- whitespacechars :: [Char]
- escapeDoubleQuotes :: String -> String
- escapeSingleQuotes :: String -> String
- escapeQuotes :: String -> String
- words' :: String -> [String]
- unwords' :: [String] -> String
- stripquotes :: String -> String
- isSingleQuoted :: [Char] -> Bool
- isDoubleQuoted :: [Char] -> Bool
- unbracket :: String -> String
- concatTopPadded :: [String] -> String
- concatBottomPadded :: [String] -> String
- vConcatRightAligned :: [String] -> String
- padtop :: Int -> String -> String
- padbottom :: Int -> String -> String
- padleft :: Int -> String -> String
- padright :: Int -> String -> String
- cliptopleft :: Int -> Int -> String -> String
- fitto :: Int -> Int -> String -> String
- first3 :: (t, t1, t2) -> t
- second3 :: (t, t1, t2) -> t1
- third3 :: (t, t1, t2) -> t2
- first4 :: (t, t1, t2, t3) -> t
- second4 :: (t, t1, t2, t3) -> t1
- third4 :: (t, t1, t2, t3) -> t2
- fourth4 :: (t, t1, t2, t3) -> t3
- first5 :: (t, t1, t2, t3, t4) -> t
- second5 :: (t, t1, t2, t3, t4) -> t1
- third5 :: (t, t1, t2, t3, t4) -> t2
- fourth5 :: (t, t1, t2, t3, t4) -> t3
- fifth5 :: (t, t1, t2, t3, t4) -> t4
- difforzero :: (Num a, Ord a) => a -> a -> a
- regexMatch :: String -> String -> Maybe (RegexResult, MatchList)
- regexMatchCI :: String -> String -> Maybe (RegexResult, MatchList)
- regexMatches :: String -> String -> Bool
- regexMatchesCI :: String -> String -> Bool
- containsRegex :: String -> String -> Bool
- regexReplace :: String -> String -> String -> String
- regexReplaceCI :: String -> String -> String -> String
- regexReplaceBy :: String -> (String -> String) -> String -> String
- regexToCaseInsensitive :: String -> String
- regexSplit :: String -> String -> [String]
- regexMatchesRegexCompat :: String -> String -> Bool
- regexMatchesCIRegexCompat :: String -> String -> Bool
- splitAtElement :: Eq a => a -> [a] -> [[a]]
- root :: Tree a -> a
- subs :: Tree a -> Forest a
- branches :: Tree a -> Forest a
- leaves :: Tree a -> [a]
- subtreeat :: Eq a => a -> Tree a -> Maybe (Tree a)
- subtreeinforest :: Eq a => a -> [Tree a] -> Maybe (Tree a)
- treeprune :: Int -> Tree a -> Tree a
- treemap :: (a -> b) -> Tree a -> Tree b
- treefilter :: (a -> Bool) -> Tree a -> Tree a
- treeany :: (a -> Bool) -> Tree a -> Bool
- showtree :: Show a => Tree a -> String
- showforest :: Show a => Forest a -> String
- newtype FastTree a = T (Map a (FastTree a))
- emptyTree :: FastTree a
- mergeTrees :: Ord a => FastTree a -> FastTree a -> FastTree a
- treeFromPath :: [a] -> FastTree a
- treeFromPaths :: Ord a => [[a]] -> FastTree a
- strace :: Show a => a -> a
- ltrace :: Show a => String -> a -> a
- mtrace :: (Monad m, Show a) => a -> m a
- traceWith :: (a -> String) -> a -> a
- ptrace :: String -> GenParser Char st ()
- debugLevel :: Int
- dbg :: Show a => String -> a -> a
- dbg0 :: Show a => String -> a -> a
- dbg1 :: Show a => String -> a -> a
- dbg2 :: Show a => String -> a -> a
- dbgAt :: Show a => Int -> String -> a -> a
- dbgAtM :: Show a => Int -> String -> a -> IO ()
- dbgshow :: Show a => Int -> String -> a -> a
- dbgppshow :: Show a => Int -> String -> a -> a
- dbgExit :: Show a => String -> a -> a
- pdbg :: Int -> String -> ParsecT [Char] st Identity ()
- choice' :: [GenParser tok st a] -> GenParser tok st a
- parsewith :: Parser a -> String -> Either ParseError a
- parseWithCtx :: b -> GenParser Char b a -> String -> Either ParseError a
- fromparse :: Either ParseError a -> a
- parseerror :: ParseError -> a
- showParseError :: ParseError -> String
- showDateParseError :: ParseError -> String
- nonspace :: GenParser Char st Char
- spacenonewline :: GenParser Char st Char
- restofline :: GenParser Char st String
- eolof :: GenParser Char st ()
- getCurrentLocalTime :: IO LocalTime
- testName :: Test -> String
- flattenTests :: Test -> [Test]
- filterTests :: (Test -> Bool) -> Test -> Test
- is :: (Eq a, Show a) => a -> a -> Assertion
- assertParse :: Either ParseError a -> Assertion
- assertParseFailure :: Either ParseError a -> Assertion
- assertParseEqual :: (Show a, Eq a) => Either ParseError a -> a -> Assertion
- printParseError :: Show a => a -> IO ()
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- applyN :: Int -> (a -> a) -> a -> a
- expandPath :: MonadIO m => FilePath -> FilePath -> m FilePath
- firstJust :: Eq a => [Maybe a] -> Maybe a
- readFile' :: FilePath -> IO String
- trace :: String -> a -> a
- type SystemString = String
- fromSystemString :: SystemString -> String
- toSystemString :: String -> SystemString
- error' :: String -> a
- userError' :: String -> IOError
- ppShow :: Show a => a -> String
Documentation
stripbrackets :: String -> String Source
elideRight :: Int -> [Char] -> [Char] Source
quoteIfSpaced :: String -> String Source
Wrap a string in double quotes, and -prefix any embedded single quotes, if it contains whitespace and is not already single- or double-quoted.
quoteIfNeeded :: [Char] -> [Char] Source
Double-quote this string if it contains whitespace, single quotes or double-quotes, escaping the quotes as needed.
singleQuoteIfNeeded :: [Char] -> [Char] Source
Single-quote this string if it contains whitespace or double-quotes. No good for strings containing single quotes.
quotechars :: [Char] Source
whitespacechars :: [Char] Source
escapeDoubleQuotes :: String -> String Source
escapeSingleQuotes :: String -> String Source
escapeQuotes :: String -> String Source
words' :: String -> [String] Source
Quote-aware version of words - don't split on spaces which are inside quotes. NB correctly handles "a'b" but not "''a''". Can raise an error if parsing fails.
unwords' :: [String] -> String Source
Quote-aware version of unwords - single-quote strings which contain whitespace
stripquotes :: String -> String Source
Strip one matching pair of single or double quotes on the ends of a string.
isSingleQuoted :: [Char] -> Bool Source
isDoubleQuoted :: [Char] -> Bool Source
concatTopPadded :: [String] -> String Source
Join multi-line strings as side-by-side rectangular strings of the same height, top-padded.
concatBottomPadded :: [String] -> String Source
Join multi-line strings as side-by-side rectangular strings of the same height, bottom-padded.
vConcatRightAligned :: [String] -> String Source
Compose strings vertically and right-aligned.
padtop :: Int -> String -> String Source
Convert a multi-line string to a rectangular string top-padded to the specified height.
padbottom :: Int -> String -> String Source
Convert a multi-line string to a rectangular string bottom-padded to the specified height.
padleft :: Int -> String -> String Source
Convert a multi-line string to a rectangular string left-padded to the specified width.
padright :: Int -> String -> String Source
Convert a multi-line string to a rectangular string right-padded to the specified width.
cliptopleft :: Int -> Int -> String -> String Source
Clip a multi-line string to the specified width and height from the top left.
fitto :: Int -> Int -> String -> String Source
Clip and pad a multi-line string to fill the specified width and height.
difforzero :: (Num a, Ord a) => a -> a -> a Source
regexMatch :: String -> String -> Maybe (RegexResult, MatchList) Source
regexMatchCI :: String -> String -> Maybe (RegexResult, MatchList) Source
regexMatches :: String -> String -> Bool Source
regexMatchesCI :: String -> String -> Bool Source
containsRegex :: String -> String -> Bool Source
regexSplit :: String -> String -> [String] Source
regexMatchesRegexCompat :: String -> String -> Bool Source
regexMatchesCIRegexCompat :: String -> String -> Bool Source
splitAtElement :: Eq a => a -> [a] -> [[a]] Source
subtreeat :: Eq a => a -> Tree a -> Maybe (Tree a) Source
get the sub-tree rooted at the first (left-most, depth-first) occurrence of the specified node value
subtreeinforest :: Eq a => a -> [Tree a] -> Maybe (Tree a) Source
get the sub-tree for the specified node value in the first tree in forest in which it occurs.
treefilter :: (a -> Bool) -> Tree a -> Tree a Source
remove all subtrees whose nodes do not fulfill predicate
showforest :: Show a => Forest a -> String Source
show a compact ascii representation of a forest
An efficient-to-build tree suggested by Cale Gibbard, probably better than accountNameTreeFrom.
treeFromPath :: [a] -> FastTree a Source
treeFromPaths :: Ord a => [[a]] -> FastTree a Source
strace :: Show a => a -> a Source
Trace (print on stdout at runtime) a showable value. (for easily tracing in the middle of a complex expression)
mtrace :: (Monad m, Show a) => a -> m a Source
Monadic trace - like strace, but works as a standalone line in a monad.
ptrace :: String -> GenParser Char st () Source
Parsec trace - show the current parsec position and next input, and the provided label if it's non-null.
debugLevel :: Int Source
Global debug level, which controls the verbosity of debug output
on the console. The default is 0 meaning no debug output. The
--debug
command line flag sets it to 1, or --debug=N
sets it to
a higher value (note: not --debug N
for some reason). This uses
unsafePerformIO and can be accessed from anywhere and before normal
command-line processing. After command-line processing, it is also
available as the debug_
field of CliOpts
.
dbg :: Show a => String -> a -> a Source
Print a message and a showable value to the console if the global debug level is non-zero. Uses unsafePerformIO.
dbgAt :: Show a => Int -> String -> a -> a Source
Print a message and a showable value to the console if the global debug level is at or above the specified level. Uses unsafePerformIO.
dbgshow :: Show a => Int -> String -> a -> a Source
Print a showable value to the console, with a message, if the debug level is at or above the specified level (uses unsafePerformIO). Values are displayed with show, all on one line, which is hard to read.
dbgppshow :: Show a => Int -> String -> a -> a Source
Print a showable value to the console, with a message, if the debug level is at or above the specified level (uses unsafePerformIO). Values are displayed with ppShow, each field/constructor on its own line.
pdbg :: Int -> String -> ParsecT [Char] st Identity () Source
Print a message and parsec debug info (parse position and next input) to the console when the debug level is at or above this level. Uses unsafePerformIO. pdbgAt :: GenParser m => Float -> String -> m ()
choice' :: [GenParser tok st a] -> GenParser tok st a Source
Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.
parseWithCtx :: b -> GenParser Char b a -> String -> Either ParseError a Source
fromparse :: Either ParseError a -> a Source
parseerror :: ParseError -> a Source
showParseError :: ParseError -> String Source
spacenonewline :: GenParser Char st Char Source
restofline :: GenParser Char st String Source
flattenTests :: Test -> [Test] Source
Flatten a Test containing TestLists into a list of single tests.
filterTests :: (Test -> Bool) -> Test -> Test Source
Filter TestLists in a Test, recursively, preserving the structure.
is :: (Eq a, Show a) => a -> a -> Assertion Source
Simple way to assert something is some expected value, with no label.
assertParse :: Either ParseError a -> Assertion Source
Assert a parse result is successful, printing the parse error on failure.
assertParseFailure :: Either ParseError a -> Assertion Source
Assert a parse result is successful, printing the parse error on failure.
assertParseEqual :: (Show a, Eq a) => Either ParseError a -> a -> Assertion Source
Assert a parse result is some expected value, printing the parse error on failure.
printParseError :: Show a => a -> IO () Source
applyN :: Int -> (a -> a) -> a -> a Source
Apply a function the specified number of times. Possibly uses O(n) stack ?
expandPath :: MonadIO m => FilePath -> FilePath -> m FilePath Source
Convert a possibly relative, possibly tilde-containing file path to an absolute one, given the current directory. ~username is not supported. Leave "-" unchanged.
readFile' :: FilePath -> IO String Source
Read a file in universal newline mode, handling whatever newline convention it may contain.
The trace
function outputs the trace message given as its first argument,
before returning the second argument as its result.
For example, this returns the value of f x
but first outputs the message.
trace ("calling f with x = " ++ show x) (f x)
The trace
function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.
type SystemString = String Source
A string received from or being passed to the operating system, such as a file path, command-line argument, or environment variable name or value. With GHC versions before 7.2 on some platforms (posix) these are typically encoded. When converting, we assume the encoding is UTF-8 (cf http://www.dwheeler.com/essays/fixing-unix-linux-filenames.html#UTF8).
fromSystemString :: SystemString -> String Source
Convert a system string to an ordinary string, decoding from UTF-8 if it appears to be UTF8-encoded and GHC version is less than 7.2.
toSystemString :: String -> SystemString Source
Convert a unicode string to a system string, encoding with UTF-8 if we are on a posix platform with GHC < 7.2.
userError' :: String -> IOError Source
A SystemString-aware version of userError.