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

Description

This module contains basic type definitions

Synopsis

Documentation

type VarName = Text Source #

Variable name

type VarFormat = Maybe Text Source #

Variable format in text form. Nothing means default format.

data FormatItem Source #

String format item.

Constructors

FString Text

Verbatim text

FVariable 

Fields

data Format Source #

String format

Constructors

Format [FormatItem] 
Instances
Eq Format Source # 
Instance details

Defined in Data.Text.Format.Heavy.Types

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Show Format Source # 
Instance details

Defined in Data.Text.Format.Heavy.Types

IsString Format # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

fromString :: String -> Format #

Semigroup Format Source # 
Instance details

Defined in Data.Text.Format.Heavy.Types

Monoid Format Source # 
Instance details

Defined in Data.Text.Format.Heavy.Types

class (Default f, Show f) => IsVarFormat f where Source #

Can be used for different data types describing formats of specific types.

Minimal complete definition

parseVarFormat

Methods

parseVarFormat :: Text -> Either String f Source #

Left for errors.

class Formatable a where Source #

Value that can be formatted to be substituted into format string.

Minimal complete definition

formatVar

Methods

formatVar Source #

Arguments

:: VarFormat

Variable format specification in text form. Nothing is for default format.

-> a

Variable value.

-> Either String Builder

Left for errors in variable format syntax, or errors during formatting.

Format variable according to format specification. This function should usually parse format specification by itself.

Instances
Formatable Bool Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Double Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Float Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Int Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Int8 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Int16 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Int32 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Int64 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Integer Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Word8 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Word16 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Word32 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Word64 Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable () Source #

Unit type is formatted as empty string

Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable String Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable ByteString Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable ByteString Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Text Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable Text Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Formatable ZonedTime Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable LocalTime Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable TimeOfDay Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable TimeZone Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable UTCTime Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable Day Source # 
Instance details

Defined in Data.Text.Format.Heavy.Time

Formatable Variable Source # 
Instance details

Defined in Data.Text.Format.Heavy.Types

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

Defined in Data.Text.Format.Heavy.Instances

Show a => Formatable (Shown 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

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

Defined in Data.Text.Format.Heavy.Instances

data Variable Source #

Any variable that can be substituted. This type may be also used to construct heterogeneous lists: [Variable 1, Variable "x"] :: [Variable].

Constructors

Formatable a => Variable a 

formatAnyVar :: VarFormat -> Variable -> Either String Builder Source #

Format one variable according to format specification.

class VarContainer c where Source #

Data structure that contains some number of variables.

Minimal complete definition

lookupVar

Instances
VarContainer () Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

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

VarContainer DefaultValue Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

(VarContainer c1, VarContainer c2) => VarContainer (ThenCheck c1 c2) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

class VarContainer c => ClosedVarContainer c where Source #

Minimal complete definition

allVarNames

Methods

allVarNames :: c -> [VarName] Source #

Instances
ClosedVarContainer () Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

(ClosedVarContainer c1, ClosedVarContainer c2) => ClosedVarContainer (ThenCheck c1 c2) Source # 
Instance details

Defined in Data.Text.Format.Heavy.Instances

Methods

allVarNames :: ThenCheck c1 c2 -> [VarName] Source #

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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

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

Defined in Data.Text.Format.Heavy.Instances

Methods

allVarNames :: (a, b, c, d, e, f) -> [VarName] 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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

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

Defined in Data.Text.Format.Heavy.Instances

Methods

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