text-format-0.2.1.0: Text formatting

PortabilityGHC
Stabilityexperimental
Maintainerbos@mailrank.com

Data.Text.Format.Types

Contents

Description

Types for text mangling.

Synopsis

Documentation

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) 

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) 

Integer format control

newtype Hex a Source

Render an integral type in hexadecimal.

Constructors

Hex a 

Instances

Enum a => Enum (Hex a) 
Eq a => Eq (Hex a) 
Integral a => Integral (Hex a) 
Num a => Num (Hex a) 
Ord a => Ord (Hex a) 
Read a => Read (Hex a) 
Real a => Real (Hex a) 
Show a => Show (Hex a) 
Integral a => Buildable (Hex a) 

Floating point format control

data FPControl a Source

A floating point number, complete with rendering instructions.

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)) 

class RealFloat a => DispFloat a Source

Class for specifying display parameters. The type a is supposed to be an IEEE-ish (real) floating-point type with floating-point radix 2, such that the mantissa returned by decodeFloat satisfies

   2^(binExp x) <= fst (decodeFloat x) < 2^(binExp x + 1)

for x > 0, so binExp x = floatDigits x - 1. The number of decimal digits that may be required is calculated with the formula

   decDigits x = 2 + floor (floatDigits x * logBase 10 2).

The default implementation uses an approximation of logBase 10 2 sufficient for mantissae of up to several thousand bits. Nevertheless, hardcoding the values in instance declarations may yield better performance.