hledger-lib-1.33: A library providing the core functionality of hledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Utils.IO

Description

Helpers for pretty-printing haskell values, reading command line arguments, working with ANSI colours, files, and time. Uses unsafePerformIO.

Limitations: When running in GHCI, this module must be reloaded to see environmental changes. The colour scheme may be somewhat hard-coded.

Synopsis

Pretty showing/printing

pshow :: Show a => a -> String Source #

Pretty show. An easier alias for pretty-simple's pShow. This will probably show in colour if useColorOnStderr is true.

pshow' :: Show a => a -> String Source #

Monochrome version of pshow. This will never show in colour.

pprint :: Show a => a -> IO () Source #

Pretty print a showable value. An easier alias for pretty-simple's pPrint. This will print in colour if useColorOnStderr is true.

pprint' :: Show a => a -> IO () Source #

Monochrome version of pprint. This will never print in colour.

Viewing with pager

pager :: String -> IO () Source #

Display the given text on the terminal, using the user's $PAGER if the text is taller than the current terminal and stdout is interactive and TERM is not "dumb" (except on Windows, where a pager will not be used). If the text contains ANSI codes, because hledger thinks the current terminal supports those, the pager should be configured to display those, otherwise users will see junk on screen (#2015). We call "setLessR" at hledger startup to make that less likely.

setupPager :: IO () Source #

Make sure our $LESS and $MORE environment variables contain R, to help ensure the common pager less will show our ANSI output properly. less uses $LESS by default, and $MORE when it is invoked as more. What the original more program does, I'm not sure. If $PAGER is configured to something else, this probably will have no effect.

Terminal size

getTerminalHeightWidth :: IO (Maybe (Int, Int)) Source #

An alternative to ansi-terminal's getTerminalSize, based on the more robust-looking terminal-size package. Tries to get stdout's terminal's current height and width.

Command line arguments

progArgs :: [String] Source #

The command line arguments that were used at program startup. Uses unsafePerformIO.

outputFileOption :: Maybe String Source #

Read the value of the -o/--output-file command line option provided at program startup, if any, using unsafePerformIO.

hasOutputFile :: Bool Source #

Check whether the -o/--output-file option has been used at program startup with an argument other than "-", using unsafePerformIO.

ANSI color

colorOption :: String Source #

Read the value of the --color or --colour command line option provided at program startup using unsafePerformIO. If this option was not provided, returns the empty string.

useColorOnStdout :: Bool Source #

Check the IO environment to see if ANSI colour codes should be used on stdout. This is done using unsafePerformIO so it can be used anywhere, eg in low-level debug utilities, which should be ok since we are just reading. The logic is: use color if the program was started with --color=yes|always or ( the program was not started with --color=no|never and a NO_COLOR environment variable is not defined and stdout supports ANSI color and -o/--output-file was not used, or its value is "-" ).

useColorOnStderr :: Bool Source #

Like useColorOnStdout, but checks for ANSI color support on stderr, and is not affected by -o/--output-file.

color :: ColorIntensity -> Color -> String -> String Source #

Wrap a string in ANSI codes to set and reset foreground colour. ColorIntensity is Dull or Vivid (ie normal and bold). Color is one of Black, Red, Green, Yellow, Blue, Magenta, Cyan, White. Eg: color Dull Red "text".

bgColor :: ColorIntensity -> Color -> String -> String Source #

Wrap a string in ANSI codes to set and reset background colour.

colorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder Source #

Wrap a WideBuilder in ANSI codes to set and reset foreground colour.

bgColorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder Source #

Wrap a WideBuilder in ANSI codes to set and reset background colour.

bold' :: String -> String Source #

Versions of some of text-ansi's string colors/styles which are more careful to not print junk onscreen. These use our useColorOnStdout.

terminalIsLight :: Maybe Bool Source #

Detect whether the terminal currently has a light background colour, if possible, using unsafePerformIO. If the terminal is transparent, its apparent light/darkness may be different.

terminalLightness :: Maybe Float Source #

Detect the terminal's current background lightness (0..1), if possible, using unsafePerformIO. If the terminal is transparent, its apparent lightness may be different.

terminalFgColor :: Maybe (RGB Float) Source #

Detect the terminal's current foreground colour, if possible, using unsafePerformIO.

terminalBgColor :: Maybe (RGB Float) Source #

Detect the terminal's current background colour, if possible, using unsafePerformIO.

Errors

error' :: String -> a Source #

Simpler alias for errorWithoutStackTrace

usageError :: String -> a Source #

A version of errorWithoutStackTrace that adds a usage hint.

Files

embedFileRelative :: FilePath -> Q Exp Source #

Like embedFile, but takes a path relative to the package directory.

expandHomePath :: FilePath -> IO FilePath Source #

Expand a tilde (representing home directory) at the start of a file path. ~username is not supported. Can raise an error.

expandPath :: FilePath -> FilePath -> IO FilePath Source #

Given a current directory, convert a possibly relative, possibly tilde-containing file path to an absolute one. ~username is not supported. Leaves "-" unchanged. Can raise an error.

expandGlob :: FilePath -> FilePath -> IO [FilePath] Source #

Like expandPath, but treats the expanded path as a glob, and returns zero or more matched absolute file paths, alphabetically sorted. Can raise an error.

sortByModTime :: [FilePath] -> IO [FilePath] Source #

Given a list of existing file paths, sort them by modification time, most recent first.

readFileOrStdinPortably :: String -> IO Text Source #

Like readFilePortably, but read from standard input if the path is "-".

readFileStrictly :: FilePath -> IO Text Source #

Like readFilePortably, but read all of the file before proceeding.

readFilePortably :: FilePath -> IO Text Source #

Read text from a file, converting any rn line endings to n,, using the system locale's text encoding, ignoring any utf8 BOM prefix (as seen in paypal's 2018 CSV, eg) if that encoding is utf8.

Time