hledger-0.6.1: A command-line (or curses or web-based) double-entry accounting tool.Source codeContentsIndex
Ledger.Utils
Description
Provide standard imports and utilities which are useful everywhere, or needed low in the module hierarchy. This is the bottom of the dependency graph.
Synopsis
module Char
module Control.Monad
module Data.List
module Data.Maybe
module Data.Ord
module Data.Tree
module Data.Time.Clock
module Data.Time.Calendar
module Data.Time.LocalTime
module Debug.Trace
underline :: String -> String
unbracket :: String -> String
concatTopPadded :: [String] -> String
concatBottomPadded :: [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
containsRegex :: String -> String -> Bool
splitAtElement :: Eq a => a -> [a] -> [[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
strace :: Show a => a -> a
ltrace :: Show a => String -> a -> a
parsewith :: Parser a -> String -> Either ParseError a
fromparse :: Either ParseError a -> a
nonspace :: GenParser Char st Char
spacenonewline :: GenParser Char st Char
restofline :: GenParser Char st String
getCurrentLocalTime :: IO LocalTime
isLeft :: Either a b -> Bool
isRight :: Either a b -> Bool
strictReadFile :: FilePath -> IO String
module Text.Printf
module Text.RegexPR
module Test.HUnit
Documentation
module Char
module Control.Monad
module Data.List
module Data.Maybe
module Data.Ord
module Data.Tree
module Data.Time.Clock
module Data.Time.Calendar
module Data.Time.LocalTime
module Debug.Trace
underline :: String -> StringSource
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.
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
containsRegex :: String -> String -> BoolSource
splitAtElement :: Eq a => a -> [a] -> [[a]]Source
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
strace :: Show a => a -> aSource
trace (print on stdout at runtime) a showable expression (for easily tracing in the middle of a complex expression)
ltrace :: Show a => String -> a -> aSource
labelled trace - like strace, with a newline and a label prepended
parsewith :: Parser a -> String -> Either ParseError aSource
trace an expression using a custom show function
fromparse :: Either ParseError a -> aSource
nonspace :: GenParser Char st CharSource
spacenonewline :: GenParser Char st CharSource
restofline :: GenParser Char st StringSource
getCurrentLocalTime :: IO LocalTimeSource
isLeft :: Either a b -> BoolSource
isRight :: Either a b -> BoolSource
strictReadFile :: FilePath -> IO StringSource
module Text.Printf
module Text.RegexPR
module Test.HUnit
Produced by Haddock version 2.6.0