| Portability | GHC |
|---|---|
| Stability | experimental |
| Maintainer | bos@serpentine.com |
| Safe Haskell | None |
Data.Text.Format
Description
Fast, efficient, flexible support for formatting text strings.
- 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
| Bounded a => Bounded (Only a) | |
| Enum a => Enum (Only a) | |
| Eq a => Eq (Only a) | |
| Floating a => Floating (Only a) | |
| Fractional a => Fractional (Only a) | |
| Integral a => Integral (Only a) | |
| Num a => Num (Only a) | |
| Ord a => Ord (Only a) | |
| Read a => Read (Only a) | |
| Real a => Real (Only a) | |
| RealFloat a => RealFloat (Only a) | |
| RealFrac a => RealFrac (Only a) | |
| Show a => Show (Only a) | |
| Buildable a => Params (Only a) |
Types for format control
Render a value using its Show instance.
Instances
| Bounded a => Bounded (Shown a) | |
| Enum a => Enum (Shown a) | |
| Eq a => Eq (Shown a) | |
| Floating a => Floating (Shown a) | |
| Fractional a => Fractional (Shown a) | |
| Integral a => Integral (Shown a) | |
| Num a => Num (Shown a) | |
| Ord a => Ord (Shown a) | |
| Read a => Read (Shown a) | |
| Real a => Real (Shown a) | |
| RealFloat a => RealFloat (Shown a) | |
| RealFrac a => RealFrac (Shown a) | |
| Show a => Show (Shown a) | |
| Show a => Buildable (Shown a) |
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 -> BuilderSource
Render a format string and arguments to a Builder.
Format control
left :: Buildable a => Int -> Char -> a -> BuilderSource
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 -> BuilderSource
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 -> BuilderSource
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.