text-format-0.2.0.0: Text formatting

PortabilityGHC
Stabilityexperimental
Maintainerbos@mailrank.com

Data.Text.Format

Contents

Description

Fast, efficient, flexible support for formatting text strings.

Synopsis

Types

data 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 Data.Text.Format

 f :: Format
 f = "hello {}"

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

newtype Only a Source

Use this newtype wrapper for your single parameter if you are formatting a string containing exactly one substitution site.

Constructors

Only 

Fields

fromOnly :: a
 

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

newtype Fast a Source

Render a floating point number using a much faster algorithm than the default (up to 10x faster). This performance comes with a potential cost in readability, as the faster algorithm can produce strings that are longer than the default algorithm (e.g. "1.3300000000000001" instead of "1.33").

Constructors

Fast 

Fields

fromFast :: a
 

Instances

Eq a => Eq (Fast a) 
Floating a => Floating (Fast a) 
Fractional a => Fractional (Fast a) 
Num a => Num (Fast a) 
Ord a => Ord (Fast a) 
Read a => Read (Fast a) 
Real a => Real (Fast a) 
RealFloat a => RealFloat (Fast a) 
RealFrac a => RealFrac (Fast a) 
Show a => Show (Fast a) 
(RealFloat a, DispFloat a) => Buildable (Fast a) 
(RealFloat a, DispFloat a) => Buildable (Fast (FPControl a)) 

newtype Shown a Source

Render a value using its Show instance.

Constructors

Shown 

Fields

shown :: a
 

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

format :: Params ps => Format -> ps -> TextSource

Render a format string and arguments to a Text.

print :: Params ps => Format -> ps -> IO ()Source

Render a format string and arguments, then print the result.

hprint :: Params ps => Handle -> Format -> ps -> IO ()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.

Render a floating point number using normal notation, with the given number of decimal places.

Integers

Floating point numbers

exptSource

Arguments

:: (Buildable a, RealFloat a) 
=> Int

Number of digits of precision after the decimal.

-> a 
-> Builder 

Render a floating point number using scientific/engineering notation (e.g. 2.3e123).

expt_ :: (Buildable a, RealFloat a) => a -> BuilderSource

Render an integer using hexadecimal notation. (No leading 0x is added.)

fixedSource

Arguments

:: (Buildable a, RealFloat a) 
=> Int

Number of digits of precision after the decimal.

-> a 
-> Builder 

Render a floating point number using normal notation.

fixed_ :: (Buildable a, RealFloat a) => a -> BuilderSource

Render a floating point number using scientific/engineering notation (e.g. 2.3e123), with the given number of decimal places.