Safe Haskell | None |
---|
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
- escapeSingleQuotes :: String -> String
- escapeQuotes :: String -> String
- words' :: String -> [String]
- unwords' :: [String] -> String
- singleQuoteIfNeeded :: [Char] -> [Char]
- whitespacechars :: [Char]
- 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
- 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
- lstrace :: Show a => String -> a -> a
- mtrace :: (Monad m, Show a) => a -> m a
- tracewith :: (a -> String) -> a -> a
- ptrace :: String -> GenParser Char st ()
- debugLevel :: Float
- dbg :: Monad m => Float -> String -> m ()
- pdbg :: Float -> 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 -> StringSource
elideRight :: Int -> [Char] -> [Char]Source
quoteIfSpaced :: String -> StringSource
Wrap a string in single quotes, and -prefix any embedded single quotes, if it contains whitespace and is not already single- or double-quoted.
escapeQuotes :: String -> StringSource
unwords' :: [String] -> StringSource
Quote-aware version of unwords - single-quote strings which contain whitespace
singleQuoteIfNeeded :: [Char] -> [Char]Source
Single-quote this string if it contains whitespace or double-quotes
stripquotes :: String -> StringSource
Strip one matching pair of single or double quotes on the ends of a string.
isSingleQuoted :: [Char] -> BoolSource
isDoubleQuoted :: [Char] -> BoolSource
concatTopPadded :: [String] -> StringSource
Join multi-line strings as side-by-side rectangular strings of the same height, top-padded.
concatBottomPadded :: [String] -> StringSource
Join multi-line strings as side-by-side rectangular strings of the same height, bottom-padded.
vConcatRightAligned :: [String] -> StringSource
Compose strings vertically and right-aligned.
padtop :: Int -> String -> StringSource
Convert a multi-line string to a rectangular string top-padded to the specified height.
padbottom :: Int -> String -> StringSource
Convert a multi-line string to a rectangular string bottom-padded to the specified height.
padleft :: Int -> String -> StringSource
Convert a multi-line string to a rectangular string left-padded to the specified width.
padright :: Int -> String -> StringSource
Convert a multi-line string to a rectangular string right-padded to the specified width.
cliptopleft :: Int -> Int -> String -> StringSource
Clip a multi-line string to the specified width and height from the top left.
fitto :: Int -> Int -> String -> StringSource
Clip and pad a multi-line string to fill the specified width and height.
difforzero :: (Num a, Ord a) => a -> a -> aSource
regexMatch :: String -> String -> Maybe (RegexResult, MatchList)Source
regexMatchCI :: String -> String -> Maybe (RegexResult, MatchList)Source
regexMatches :: String -> String -> BoolSource
regexMatchesCI :: String -> String -> BoolSource
containsRegex :: String -> String -> BoolSource
regexSplit :: String -> String -> [String]Source
regexMatchesRegexCompat :: String -> String -> BoolSource
regexMatchesCIRegexCompat :: String -> String -> BoolSource
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 aSource
remove all subtrees whose nodes do not fulfill predicate
showforest :: Show a => Forest a -> StringSource
show a compact ascii representation of a forest
An efficient-to-build tree suggested by Cale Gibbard, probably better than accountNameTreeFrom.
treeFromPath :: [a] -> FastTree aSource
treeFromPaths :: Ord a => [[a]] -> FastTree aSource
strace :: Show a => a -> aSource
trace (print on stdout at runtime) a showable expression (for easily tracing in the middle of a complex expression)
lstrace :: Show a => String -> a -> aSource
labelled trace showable - like strace, with a label prepended
mtrace :: (Monad m, Show a) => a -> m aSource
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 string if it's non-null.
dbg :: Monad m => Float -> String -> m ()Source
Print a message to the console if the global debugLevel is greater than the level we are called with.
pdbg :: Float -> String -> ParsecT [Char] st Identity ()Source
Print a message and parsec position info to the console if the global debugLevel is greater than the level we are called with. pdbg :: GenParser m => Float -> String -> m ()
choice' :: [GenParser tok st a] -> GenParser tok st aSource
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 aSource
fromparse :: Either ParseError a -> aSource
parseerror :: ParseError -> aSource
restofline :: GenParser Char st StringSource
flattenTests :: Test -> [Test]Source
Flatten a Test containing TestLists into a list of single tests.
filterTests :: (Test -> Bool) -> Test -> TestSource
Filter TestLists in a Test, recursively, preserving the structure.
is :: (Eq a, Show a) => a -> a -> AssertionSource
Simple way to assert something is some expected value, with no label.
assertParse :: Either ParseError a -> AssertionSource
Assert a parse result is successful, printing the parse error on failure.
assertParseFailure :: Either ParseError a -> AssertionSource
Assert a parse result is successful, printing the parse error on failure.
assertParseEqual :: (Show a, Eq a) => Either ParseError a -> a -> AssertionSource
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 -> aSource
Apply a function the specified number of times. Possibly uses O(n) stack ?
expandPath :: MonadIO m => FilePath -> FilePath -> m FilePathSource
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 StringSource
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 = StringSource
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 -> StringSource
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 -> SystemStringSource
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 -> IOErrorSource
A SystemString-aware version of userError.