text-format-heavy-0.1.5.3: Full-weight string formatting library, analog of Python's string.format

Safe HaskellSafe
LanguageHaskell2010

Data.Text.Format.Heavy

Description

This is the main module of text-format-heavy library.

In most cases, you need to import only this module, and probably also the Data.Text.Format.Heavy.Time module, if you want to format time/date values.

This package exports the format function and Format data type. The Format type implements the instance of IsString, so in the code you may use formatting strings as literals, if you enable OverloadedStrings extension.

Formatting strings syntax is based on Python's string.format() syntax.

The simple usage example is

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Data.Time
import qualified Data.Text.Lazy.IO as TLIO
import Data.Text.Format.Heavy
import Data.Text.Format.Heavy.Time

main :: IO ()
main = do
  name <- getLine
  time <- getZonedTime
  TLIO.putStrLn $ format "Hello, {}! It is {:%H:%M:%S} now." (name, time)
Synopsis

Documentation

format :: VarContainer vars => Format -> vars -> Text Source #

The main formatting function. This function throws error if some error detected during format string parsing or formatting itself.

type WithDefault c = ThenCheck c DefaultValue Source #

Convenience type synonym.

data ThenCheck c1 c2 Source #

Combiled variable container, which uses parameters from c1, and if variable is not found there it will check in c2.

Constructors

ThenCheck c1 c2 

data DefaultValue Source #

Variable container which contains fixed value for any variable name.

Constructors

DefaultValue Variable 

data Shown a Source #

Values packed in Shown will be formatted using their Show instance.

For example,

formatText "values: {}." (Shown (True, False)) ==> "values: (True, False)."

Constructors

Shown 

Fields

Instances
Eq a => Eq (Shown a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

(==) :: Shown a -> Shown a -> Bool #

(/=) :: Shown a -> Shown a -> Bool #

Show a => Show (Shown a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

showsPrec :: Int -> Shown a -> ShowS #

show :: Shown a -> String #

showList :: [Shown a] -> ShowS #

Show a => Formatable (Shown a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

data Several a Source #

Container for several parameters of the same type. Example usage:

format "{} + {} = {}" $ Several [2, 3, 5]

Constructors

Several 

Fields

Instances
Eq a => Eq (Several a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

(==) :: Several a -> Several a -> Bool #

(/=) :: Several a -> Several a -> Bool #

Show a => Show (Several a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

showsPrec :: Int -> Several a -> ShowS #

show :: Several a -> String #

showList :: [Several a] -> ShowS #

Formatable a => ClosedVarContainer (Several a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable a => VarContainer (Several a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

data Single a Source #

Container for single parameter. Example usage:

format "Hello, {}!" (Single name)

Constructors

Single 

Fields

Instances
Eq a => Eq (Single a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

(==) :: Single a -> Single a -> Bool #

(/=) :: Single a -> Single a -> Bool #

Show a => Show (Single a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

showsPrec :: Int -> Single a -> ShowS #

show :: Single a -> String #

showList :: [Single a] -> ShowS #

Formatable a => ClosedVarContainer (Single a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

allVarNames :: Single a -> [VarName] Source #

Formatable a => VarContainer (Single a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable a => Formatable (Single a) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

withDefault :: VarContainer c => c -> Variable -> WithDefault c Source #

Use variables from specified container, or use default value if variable is not found in container.

optional :: VarContainer c => c -> WithDefault c Source #

Use variables from specified container, or use empty string variable is not found in container.