fmt-0.6.1.2: A new formatting library

Safe HaskellNone
LanguageHaskell2010

Fmt.Internal.Template

Description

Old-style formatting a la text-format.

Synopsis

Documentation

>>> import Fmt

format :: (HasCallStack, FormatType r) => Format -> r Source #

An old-style formatting function taken from text-format (see Data.Text.Format). Unlike format from Data.Text.Format, it can produce String and strict Text as well (and print to console too). Also it's polyvariadic:

>>> format "{} + {} = {}" 2 2 4
2 + 2 = 4

You can use arbitrary formatters:

>>> format "0x{} + 0x{} = 0x{}" (hexF 130) (hexF 270) (hexF (130+270))
0x82 + 0x10e = 0x190

formatLn :: (HasCallStack, FormatType r) => Format -> r Source #

Like format, but adds a newline.

newtype Format Source #

A format string. This is intentionally incompatible with other string types, to make it difficult to construct a format string by concatenating string fragments (a very common way to accidentally make code vulnerable to malicious data).

This type is an instance of IsString, so the easiest way to construct a query is to enable the OverloadedStrings language extension and then simply write the query in double quotes.

{-# LANGUAGE OverloadedStrings #-}

import Fmt

f :: Format
f = "hello {}"

The underlying type is Text, so literal Haskell strings that contain Unicode characters will be correctly handled.

Constructors

Format 

Fields

Instances
Eq Format Source # 
Instance details

Defined in Fmt.Internal.Template

Methods

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

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

Ord Format Source # 
Instance details

Defined in Fmt.Internal.Template

Show Format Source # 
Instance details

Defined in Fmt.Internal.Template

IsString Format Source # 
Instance details

Defined in Fmt.Internal.Template

Methods

fromString :: String -> Format #

Semigroup Format Source # 
Instance details

Defined in Fmt.Internal.Template

Monoid Format Source # 
Instance details

Defined in Fmt.Internal.Template

renderFormat :: Format -> [Builder] -> Builder Source #

Render a format string and arguments to a Builder.

class FormatType r where Source #

Something like PrintfType in Text.Printf.

Methods

format' :: Format -> [Builder] -> r Source #

Instances
FromBuilder r => FormatType r Source # 
Instance details

Defined in Fmt.Internal.Template

Methods

format' :: Format -> [Builder] -> r Source #

(Buildable a, FormatType r) => FormatType (a -> r) Source # 
Instance details

Defined in Fmt.Internal.Template

Methods

format' :: Format -> [Builder] -> a -> r Source #