Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- module Data.Text.Format.Heavy.Types
- module Data.Text.Format.Heavy.Formats
- format :: VarContainer vars => Format -> vars -> Text
- type WithDefault c = ThenCheck c DefaultValue
- data ThenCheck c1 c2 = ThenCheck c1 c2
- data DefaultValue = DefaultValue Variable
- data Shown a = Shown {
- shown :: a
- data Several a = Several {
- getSeveral :: [a]
- data Single a = Single {
- getSingle :: a
- withDefault :: VarContainer c => c -> Variable -> WithDefault c
- optional :: VarContainer c => c -> WithDefault c
Documentation
module Data.Text.Format.Heavy.Types
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.
Combiled variable container, which uses parameters from c1
,
and if variable is not found there it will check in c2
.
ThenCheck c1 c2 |
Instances
(ClosedVarContainer c1, ClosedVarContainer c2) => ClosedVarContainer (ThenCheck c1 c2) Source # | |
Defined in Data.Text.Format.Heavy.Instances allVarNames :: ThenCheck c1 c2 -> [VarName] Source # | |
(VarContainer c1, VarContainer c2) => VarContainer (ThenCheck c1 c2) Source # | |
data DefaultValue Source #
Variable container which contains fixed value for any variable name.
Instances
VarContainer DefaultValue Source # | |
Defined in Data.Text.Format.Heavy.Instances |
Values packed in Shown will be formatted using their Show instance.
For example,
formatText "values: {}." (Shown (True, False)) ==> "values: (True, False)."
Container for several parameters of the same type. Example usage:
format "{} + {} = {}" $ Several [2, 3, 5]
Several | |
|
Instances
Eq a => Eq (Several a) Source # | |
Show a => Show (Several a) Source # | |
Formatable a => ClosedVarContainer (Several a) Source # | |
Defined in Data.Text.Format.Heavy.Instances allVarNames :: Several a -> [VarName] Source # | |
Formatable a => VarContainer (Several a) Source # | |
Container for single parameter. Example usage:
format "Hello, {}!" (Single name)
Instances
Eq a => Eq (Single a) Source # | |
Show a => Show (Single a) Source # | |
Formatable a => ClosedVarContainer (Single a) Source # | |
Defined in Data.Text.Format.Heavy.Instances allVarNames :: Single a -> [VarName] Source # | |
Formatable a => VarContainer (Single a) Source # | |
Formatable a => Formatable (Single a) Source # | |
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.