| Copyright | (c) 2011 MailRank Inc. | 
|---|---|
| License | BSD-style | 
| Maintainer | bos@serpentine.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Data.Text.Format
Description
Fast, efficient, flexible support for formatting text strings.
Synopsis
- data Format
- newtype Only a = Only {- fromOnly :: a
 
- newtype Shown a = Shown {- shown :: a
 
- format :: Params ps => Format -> ps -> Text
- print :: (MonadIO m, Params ps) => Format -> ps -> m ()
- hprint :: (MonadIO m, Params ps) => Handle -> Format -> ps -> m ()
- build :: Params ps => Format -> ps -> Builder
- left :: Buildable a => Int -> Char -> a -> Builder
- right :: Buildable a => Int -> Char -> a -> Builder
- hex :: Integral a => a -> Builder
- expt :: Real a => Int -> a -> Builder
- fixed :: Real a => Int -> a -> Builder
- prec :: Real a => Int -> a -> Builder
- shortest :: Real a => a -> Builder
Types
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 Data.Text.Format
f :: Format
f = "hello {}"The underlying type is Text, so literal Haskell strings that
 contain Unicode characters will be correctly handled.
Use this newtype wrapper for your single parameter if you are
 formatting a string containing exactly one substitution site.
Instances
Types for format control
Render a value using its Show instance.
Instances
Rendering
print :: (MonadIO m, Params ps) => Format -> ps -> m () Source #
Render a format string and arguments, then print the result.
hprint :: (MonadIO m, Params ps) => Handle -> Format -> ps -> m () Source #
Render a format string and arguments, then print the result to the given file handle.
build :: Params ps => Format -> ps -> Builder Source #
Render a format string and arguments to a Builder.
Format control
left :: Buildable a => Int -> Char -> a -> Builder Source #
Pad the left hand side of a string until it reaches k
 characters wide, if necessary filling with character c.
right :: Buildable a => Int -> Char -> a -> Builder Source #
Pad the right hand side of a string until it reaches k
 characters wide, if necessary filling with character c.
Integers
hex :: Integral a => a -> Builder Source #
Render an integer using hexadecimal notation. (No leading "0x" is added.)
Floating point numbers
Render a floating point number using scientific/engineering
 notation (e.g. 2.3e123), with the given number of decimal places.
Render a floating point number using normal notation, with the given number of decimal places.
Render a floating point number, with the given number of digits
 of precision.  Uses decimal notation for values between 0.1 and
 9,999,999, and scientific notation otherwise.