PyF-0.9.0.3: Quasiquotations for a python like interpolated string formatter
Safe HaskellNone
LanguageHaskell2010

PyF.Class

Description

You want to add formatting support for your custom type. This is the right module.

In PyF, formatters are in three categories:

  • Integral numbers, which are numbers without fractional part
  • Fractional numbers, which are numbers with a fractional part
  • String, which represents text.

The formatting can be either explicit or implicit. For example:

>>> let x = 10 in [fmt|{x}|]
10

Is an implicit formating to number, but:

>>> let x = 10 in [fmt|{x:d}|]

Is an explicit formatting to Integral numbers, using d.

Implicit formatting will only format to either Integral, Fractional or text, and this choice is done by the (open) type family PyFCategory.

This modules also provides 3 type class for formatting.

Synopsis

Default formatting classification

data PyFCategory Source #

The three categories of formatting in PyF

Constructors

PyFIntegral

Format as an integral, no fractional part, precise value

PyFFractional

Format as a fractional, approximate value with a fractional part

PyFString

Format as a string

type family PyFClassify t :: PyFCategory Source #

Classify a type to a PyFCategory This classification will be used to decide which formatting to use when no type specifier in provided.

Instances

Instances details
type PyFClassify Char Source # 
Instance details

Defined in PyF.Class

type PyFClassify Double Source # 
Instance details

Defined in PyF.Class

type PyFClassify Float Source # 
Instance details

Defined in PyF.Class

type PyFClassify Int Source # 
Instance details

Defined in PyF.Class

type PyFClassify Int8 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Int16 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Int32 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Int64 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Integer Source # 
Instance details

Defined in PyF.Class

type PyFClassify Natural Source # 
Instance details

Defined in PyF.Class

type PyFClassify Word Source # 
Instance details

Defined in PyF.Class

type PyFClassify Word8 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Word16 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Word32 Source # 
Instance details

Defined in PyF.Class

type PyFClassify Word64 Source # 
Instance details

Defined in PyF.Class

type PyFClassify String Source # 
Instance details

Defined in PyF.Class

type PyFClassify ByteString Source # 
Instance details

Defined in PyF.Class

type PyFClassify ByteString Source # 
Instance details

Defined in PyF.Class

type PyFClassify Text Source # 
Instance details

Defined in PyF.Class

type PyFClassify Text Source # 
Instance details

Defined in PyF.Class

type PyFClassify NominalDiffTime Source # 
Instance details

Defined in PyF.Class

type PyFClassify DiffTime Source # 
Instance details

Defined in PyF.Class

type PyFClassify (Ratio i) Source # 
Instance details

Defined in PyF.Class

String formatting

class PyFToString t where Source #

Convert a type to string This is used for the string formatting.

Methods

pyfToString :: t -> String Source #

Instances

Instances details
PyFToString Char Source # 
Instance details

Defined in PyF.Class

Show t => PyFToString t Source #

Default instance. Convert any type with a 'Show instance.

Instance details

Defined in PyF.Class

Methods

pyfToString :: t -> String Source #

PyFToString String Source # 
Instance details

Defined in PyF.Class

PyFToString ByteString Source # 
Instance details

Defined in PyF.Class

PyFToString ByteString Source # 
Instance details

Defined in PyF.Class

PyFToString Text Source # 
Instance details

Defined in PyF.Class

PyFToString Text Source # 
Instance details

Defined in PyF.Class

Real formatting (with optional fractional part)

class PyfFormatFractional a where Source #

Apply a fractional formatting to any type.

A default instance for any Real is provided which internally converts to Double, which may not be efficient or results in rounding errors.

You can provide your own instance and internally use formatFractional which does have the same signatures as pyfFormatFractional but with a RealFrac constraint.

Methods

pyfFormatFractional Source #

Arguments

:: Format t t' 'Fractional 
-> SignMode

Sign formatting

-> Maybe (Int, AlignMode k, Char)

Padding

-> Maybe (Int, Char)

Grouping

-> Maybe Int

Precision

-> a 
-> String 

Instances

Instances details
PyfFormatFractional Double Source #

This instance does not do any conversion.

Instance details

Defined in PyF.Class

Methods

pyfFormatFractional :: forall (t :: AltStatus) (t' :: UpperStatus) (k :: AlignForString). Format t t' 'Fractional -> SignMode -> Maybe (Int, AlignMode k, Char) -> Maybe (Int, Char) -> Maybe Int -> Double -> String Source #

PyfFormatFractional Float Source #

This instance does not do any conversion.

Instance details

Defined in PyF.Class

Methods

pyfFormatFractional :: forall (t :: AltStatus) (t' :: UpperStatus) (k :: AlignForString). Format t t' 'Fractional -> SignMode -> Maybe (Int, AlignMode k, Char) -> Maybe (Int, Char) -> Maybe Int -> Float -> String Source #

Real t => PyfFormatFractional t Source #

Default instance working for any Real. Internally it converts the type to Double.

Instance details

Defined in PyF.Class

Methods

pyfFormatFractional :: forall (t0 :: AltStatus) (t' :: UpperStatus) (k :: AlignForString). Format t0 t' 'Fractional -> SignMode -> Maybe (Int, AlignMode k, Char) -> Maybe (Int, Char) -> Maybe Int -> t -> String Source #

Integral formatting

class PyfFormatIntegral i where Source #

Apply an integral formatting to any type.

A default instance for any Integral is provided.

You can provide your own instance and internally use formatIntegral which does have the same signatures as pyfFormatIntegral but with an Integral constraint.

Methods

pyfFormatIntegral Source #

Arguments

:: Format t t' 'Integral 
-> SignMode

Sign formatting

-> Maybe (Int, AlignMode k, Char)

Padding

-> Maybe (Int, Char)

Grouping

-> i 
-> String 

Instances

Instances details
PyfFormatIntegral Char Source #

Returns the numerical value of a Char >>> [fmt|{a:d}|] 97

Instance details

Defined in PyF.Class

Methods

pyfFormatIntegral :: forall (t :: AltStatus) (t' :: UpperStatus) (k :: AlignForString). Format t t' 'Integral -> SignMode -> Maybe (Int, AlignMode k, Char) -> Maybe (Int, Char) -> Char -> String Source #

Integral t => PyfFormatIntegral t Source #

Default instance for any Integral.

Instance details

Defined in PyF.Class

Methods

pyfFormatIntegral :: forall (t0 :: AltStatus) (t' :: UpperStatus) (k :: AlignForString). Format t0 t' 'Integral -> SignMode -> Maybe (Int, AlignMode k, Char) -> Maybe (Int, Char) -> t -> String Source #