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

Safe HaskellNone
LanguageHaskell2010

Data.Text.Format.Heavy.Instances

Contents

Description

This module contains Formatable and VarContainer instances for most used types.

Synopsis

Utility data types

data Single a Source #

Container for single parameter. Example usage:

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

Constructors

Single 

Fields

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 # 

Methods

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

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

Show a => Show (Several a) Source # 

Methods

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

show :: Several a -> String #

showList :: [Several a] -> ShowS #

Formatable a => VarContainer (Several a) Source # 

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 # 

Methods

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

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

Show a => Show (Shown a) Source # 

Methods

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

show :: Shown a -> String #

showList :: [Shown a] -> ShowS #

Show a => Formatable (Shown a) Source # 

Generic formatters

genericIntFormat :: Integral a => VarFormat -> a -> Either String Builder Source #

Generic formatter for integer types

genericFloatFormat :: RealFloat a => VarFormat -> a -> Either String Builder Source #

Generic formatter for floating-point types

Orphan instances

IsString Format Source # 

Methods

fromString :: String -> Format #

VarContainer () Source # 

Methods

lookupVar :: VarName -> () -> Maybe Variable Source #

Formatable Bool Source # 
Formatable Double Source # 
Formatable Float Source # 
Formatable Int Source # 
Formatable Int8 Source # 
Formatable Int16 Source # 
Formatable Int32 Source # 
Formatable Int64 Source # 
Formatable Integer Source # 
Formatable Word8 Source # 
Formatable Word16 Source # 
Formatable Word32 Source # 
Formatable Word64 Source # 
Formatable () Source #

Unit type is formatted as empty string

Formatable String Source # 
Formatable ByteString Source # 
Formatable ByteString Source # 
Formatable Text Source # 
Formatable Text Source # 
IsVarFormat BoolFormat Source # 
IsVarFormat GenericFormat Source # 
Formatable x => VarContainer [(Text, x)] Source # 

Methods

lookupVar :: VarName -> [(Text, x)] -> Maybe Variable Source #

Formatable a => VarContainer (Maybe a) Source #

Maybe container contains one variable (named 0); Nothing contains an empty string.

Formatable a => Formatable (Maybe a) Source # 
(Formatable a, Formatable b) => VarContainer (a, b) Source # 

Methods

lookupVar :: VarName -> (a, b) -> Maybe Variable Source #

Formatable x => VarContainer (Map Text x) Source # 
(Formatable a, Formatable b) => Formatable (Either a b) Source # 
(Formatable a, Formatable b, Formatable c) => VarContainer (a, b, c) Source # 

Methods

lookupVar :: VarName -> (a, b, c) -> Maybe Variable Source #

(Formatable a, Formatable b, Formatable c, Formatable d) => VarContainer (a, b, c, d) Source # 

Methods

lookupVar :: VarName -> (a, b, c, d) -> Maybe Variable Source #

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e) => VarContainer (a, b, c, d, e) Source # 

Methods

lookupVar :: VarName -> (a, b, c, d, e) -> Maybe Variable Source #

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f) => VarContainer (a, b, c, d, e, f) Source # 

Methods

lookupVar :: VarName -> (a, b, c, d, e, f) -> Maybe Variable Source #

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f, Formatable g) => VarContainer (a, b, c, d, e, f, g) Source # 

Methods

lookupVar :: VarName -> (a, b, c, d, e, f, g) -> Maybe Variable Source #