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

Safe HaskellSafe
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
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

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 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

Combinators

data DefaultValue Source #

Variable container which contains fixed value for any variable name.

Constructors

DefaultValue Variable 

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 

type WithDefault c = ThenCheck c DefaultValue Source #

Convenience type synonym.

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.

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 # 
Instance details

Methods

fromString :: String -> Format #

ClosedVarContainer () Source # 
Instance details

Methods

allVarNames :: () -> [VarName] Source #

VarContainer () Source # 
Instance details

Methods

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

Formatable Bool Source # 
Instance details

Formatable Double Source # 
Instance details

Formatable Float Source # 
Instance details

Formatable Int Source # 
Instance details

Formatable Int8 Source # 
Instance details

Formatable Int16 Source # 
Instance details

Formatable Int32 Source # 
Instance details

Formatable Int64 Source # 
Instance details

Formatable Integer Source # 
Instance details

Formatable Word8 Source # 
Instance details

Formatable Word16 Source # 
Instance details

Formatable Word32 Source # 
Instance details

Formatable Word64 Source # 
Instance details

Formatable () Source #

Unit type is formatted as empty string

Instance details

Formatable String Source # 
Instance details

Formatable ByteString Source # 
Instance details

Formatable ByteString Source # 
Instance details

Formatable Text Source # 
Instance details

Formatable Text Source # 
Instance details

IsVarFormat BoolFormat Source # 
Instance details

IsVarFormat GenericFormat Source # 
Instance details

Formatable x => ClosedVarContainer [(Text, x)] Source # 
Instance details

Methods

allVarNames :: [(Text, x)] -> [VarName] Source #

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

Methods

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

Formatable x => VarContainer [(Text, x)] Source # 
Instance details

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.

Instance details

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

(Formatable a, Formatable b) => ClosedVarContainer (a, b) Source # 
Instance details

Methods

allVarNames :: (a, b) -> [VarName] Source #

Formatable x => ClosedVarContainer (Map Text x) Source # 
Instance details

Methods

allVarNames :: Map Text x -> [VarName] Source #

(Formatable a, Formatable b) => VarContainer (a, b) Source # 
Instance details

Methods

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

Formatable x => VarContainer (Map Text x) Source # 
Instance details

(Formatable a, Formatable b) => Formatable (Either a b) Source # 
Instance details

(Formatable a, Formatable b, Formatable c) => ClosedVarContainer (a, b, c) Source # 
Instance details

Methods

allVarNames :: (a, b, c) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d) => ClosedVarContainer (a, b, c, d) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e) => ClosedVarContainer (a, b, c, d, e) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f) => ClosedVarContainer (a, b, c, d, e, f) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e, f) -> [VarName] Source #

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

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) => ClosedVarContainer (a, b, c, d, e, f, g) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e, f, g) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f, Formatable g, Formatable h) => ClosedVarContainer (a, b, c, d, e, f, g, h) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e, f, g, h) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f, Formatable g, Formatable h, Formatable i) => ClosedVarContainer (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e, f, g, h, i) -> [VarName] Source #

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

Methods

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

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f, Formatable g, Formatable h, Formatable i, Formatable j) => ClosedVarContainer (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

allVarNames :: (a, b, c, d, e, f, g, h, i, j) -> [VarName] Source #

(Formatable a, Formatable b, Formatable c, Formatable d, Formatable e, Formatable f, Formatable g, Formatable h, Formatable i, Formatable j) => VarContainer (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

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