hledger-lib-0.22: Core data types, parsers and utilities for the hledger accounting tool.

Safe HaskellNone

Hledger.Utils

Description

Standard imports and utilities which are useful everywhere, or needed low in the module hierarchy. This is the bottom of hledger's module graph.

Synopsis

Documentation

lowercase :: [Char] -> [Char]Source

uppercase :: [Char] -> [Char]Source

strip :: [Char] -> StringSource

lstrip :: String -> StringSource

rstrip :: [Char] -> [Char]Source

stripbrackets :: String -> StringSource

elideLeft :: Int -> [Char] -> [Char]Source

elideRight :: Int -> [Char] -> [Char]Source

underline :: String -> StringSource

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.

escapeSingleQuotes :: String -> StringSource

escapeQuotes :: String -> StringSource

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

unbracket :: String -> StringSource

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

regexReplace :: String -> String -> String -> StringSource

regexReplaceCI :: String -> String -> String -> StringSource

regexReplaceBy :: String -> (String -> String) -> String -> StringSource

regexToCaseInsensitive :: String -> StringSource

regexSplit :: String -> String -> [String]Source

regexMatchesRegexCompat :: String -> String -> BoolSource

regexMatchesCIRegexCompat :: String -> String -> BoolSource

splitAtElement :: Eq a => a -> [a] -> [[a]]Source

root :: Tree a -> aSource

subs :: Tree a -> Forest aSource

branches :: Tree a -> Forest aSource

leaves :: Tree a -> [a]Source

List just the leaf nodes of a tree

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.

treeprune :: Int -> Tree a -> Tree aSource

remove all nodes past a certain depth

treemap :: (a -> b) -> Tree a -> Tree bSource

apply f to all tree nodes

treefilter :: (a -> Bool) -> Tree a -> Tree aSource

remove all subtrees whose nodes do not fulfill predicate

treeany :: (a -> Bool) -> Tree a -> BoolSource

is predicate true in any node of tree ?

showtree :: Show a => Tree a -> StringSource

show a compact ascii representation of a tree

showforest :: Show a => Forest a -> StringSource

show a compact ascii representation of a forest

newtype FastTree a Source

An efficient-to-build tree suggested by Cale Gibbard, probably better than accountNameTreeFrom.

Constructors

T (Map a (FastTree a)) 

Instances

Eq a => Eq (FastTree a) 
Ord a => Ord (FastTree a) 
Show a => Show (FastTree a) 

mergeTrees :: Ord a => FastTree a -> FastTree a -> FastTree aSource

treeFromPaths :: Ord a => [[a]] -> FastTree aSource

strace :: Show a => a -> aSource

Trace (print on stdout at runtime) a showable value. (for easily tracing in the middle of a complex expression)

ltrace :: Show a => String -> a -> aSource

Labelled trace - 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.

traceWith :: (a -> String) -> a -> aSource

Custom trace - like strace, with a custom show function.

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 :: IntSource

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

Print a message and a showable value to the console if the global debug level is non-zero. Uses unsafePerformIO.

dbgshow :: Show a => Int -> String -> a -> aSource

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

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.

dbgpprint :: Data a => Int -> String -> a -> aSource

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 pprint. Field names are not shown, but the output is compact with smart line wrapping, long data elided, and slow calculations timed out.

dbgExit :: Show a => String -> a -> aSource

Like dbg, then exit the program. Uses unsafePerformIO.

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 aSource

Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.

parsewith :: Parser a -> String -> Either ParseError aSource

parseWithCtx :: b -> GenParser Char b a -> String -> Either ParseError aSource

fromparse :: Either ParseError a -> aSource

nonspace :: GenParser Char st CharSource

restofline :: GenParser Char st StringSource

eolof :: GenParser Char st ()Source

testName :: Test -> StringSource

Get a Test's label, or the empty string.

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

isLeft :: Either a b -> BoolSource

isRight :: Either a b -> BoolSource

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.

firstJust :: Eq a => [Maybe a] -> Maybe aSource

readFile' :: FilePath -> IO StringSource

Read a file in universal newline mode, handling whatever newline convention it may contain.

trace :: String -> a -> a

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.

error' :: String -> aSource

A SystemString-aware version of error.

userError' :: String -> IOErrorSource

A SystemString-aware version of userError.

ppShow :: Show a => a -> String

Convert a generic value into a pretty String, if possible.