typelits-printf-0.2.0.0: Type-safe printf from parsing GHC TypeLits Symbol
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

GHC.TypeLits.Printf

Description

An extensible and type-safe printf from parsing GHC TypeLits Symbol literals, matching the semantics of printf from Text.Printf in base. The difference is that your printfs will always fail to compile if given arguments of the wrong type (or too many or too little arguments). It also allows you to use types to help your development, by telling you the type of arguments it expects and how many when queried with :t or with typed holes. See documentation in Text.Printf for details on how this formats items of various types, and the differences with C printf(3).

See printf for the main function.

You can extend functionality with formatting for your own types by providing instances of FormatType.

Also in this module is pfmt, which allows you to format individual items according to a single format specifier.

Synopsis

Printf

printf :: forall str fun. Printf str fun => fun Source #

"Type-safe printf". Call it like printf @"you have %.02f dollars, %s".

>>> putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi

Looking at its type:

>>> :t printf @"You have %.2f dollars, %s"
(FormatType "f" arg1, FormatType "s" arg2)
  => arg1 -> arg2 -> String

It tells you that the result is an arg1 -> arg2 -> String: take two arguments, and return a String. The first argument must be an instance of FormatType "f" (things that can be formatted by %f) and the second argument must be an instance of FormatType "s" (things that can be formatted by %s).

We can see this in action by progressively applying arguments:

>>> :t printf @"You have %.2f dollars, %s" 3.62
FormatType "s" arg1 => arg1 -> String
>>> :t printf @"You have %.2f dollars, %s" 3.62 "Luigi"
String

The type errors for forgetting to apply an argument (or applying too many arguments) are pretty clear:

>>> putStrLn $ printf @"You have %.2f dollars, %s"
-- ERROR: Call to printf missing argument fulfilling "%.2f"
-- Either provide an argument or rewrite the format string to not expect
-- one.
>>> putStrLn $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s"
-- Either provide an argument or rewrite the format string to not expect
-- one.
>>> putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>> putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi" 72
-- ERROR: An extra argument of type Integer was given to a call to printf
-- Either remove the argument, or rewrite the format string to include the
-- appropriate hole.

If you want to see some useful error messages for feedback, pHelp can be useful:

>>> pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s"
-- Either provide an argument or rewrite the format string to not expect
-- one.

Note that this also supports the "interpret as an IO action to print out results" functionality that Text.Printf supports. This also supports returning strict Text and lazy Text as well.

printf_ :: Printf str fun => p str -> fun Source #

A version of printf taking an explicit proxy, which allows usage without TypeApplications

>>> putStrLn $ printf_ (Proxy :: Proxy "You have %.2f dollars, %s") 3.62 "Luigi"
You have 3.62 dollars, Luigi

data PHelp Source #

A useful tool for helping the type system give useful errors for printf:

>>> printf @"You have ".2f" dollars, %s" 3.26 :: PHelp
-- ERROR: Call to printf missing argument fulfilling "%s"
-- Either provide an argument or rewrite the format string to not expect
-- one.

Mostly useful if you want to force a useful type error to help see what is going on.

See also pHelp

Instances

Instances details
a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) PHelp Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> PHelp Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) PHelp Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> PHelp Source #

pHelp :: PHelp -> String Source #

A useful helper function for helping the type system give useful errors for printf:

>>> pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s"
-- Either provide an argument or rewrite the format string to not expect
-- one.

Mostly useful if you want to force a useful type error to help see what is going on.

class FormatFun (ffs :: [Either Symbol FieldFormat]) fun Source #

The typeclass supporting polyarity used by printf. It works in mostly the same way as PrintfType from Text.Printf, and similar the same as FormatF. Ideally, you will never have to run into this typeclass or have to deal with it directly.

Every item in the first argument of FormatFun is a chunk of the formatting string, split between format holes (Right) and string chunks (Left).

If you want to see some useful error messages for feedback, pHelp can be useful:

>>> pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s"
-- Either provide an argument or rewrite the format string to not expect
-- one.

Minimal complete definition

formatFun

Instances

Instances details
(TypeError ('Text "Result type of a call to printf not sufficiently inferred." :$$: 'Text "Please provide an explicit type annotation or other way to help inference.") :: Constraint) => FormatFun ('[] :: [Either Symbol FieldFormat]) () Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> () Source #

a ~ String => FormatFun ('[] :: [Either Symbol FieldFormat]) a Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> a Source #

a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> Text Source #

a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> Text Source #

a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) PHelp Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> PHelp Source #

a ~ () => FormatFun ('[] :: [Either Symbol FieldFormat]) (IO a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> IO a Source #

(TypeError ((('Text "An extra argument of type " :<>: 'ShowType a) :<>: 'Text " was given to a call to printf.") :$$: 'Text "Either remove the argument, or rewrite the format string to include the appropriate hole") :: Constraint) => FormatFun ('[] :: [Either Symbol FieldFormat]) (a -> b) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> a -> b Source #

(KnownSymbol str, FormatFun ffs fun) => FormatFun (('Left str :: Either Symbol FieldFormat) ': ffs) fun Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Left str ': ffs) -> String -> fun Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) PHelp Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> PHelp Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> Text Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> Text Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) () Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> () Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) String Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> String Source #

(afun ~ (arg -> fun), Reflect ff, ff ~ 'FF f w p m c, FormatType c arg, FormatFun ffs fun) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) afun Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> afun Source #

(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) (IO a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p ('Right ff ': ffs) -> String -> IO a Source #

Formattable things

class FormatType (t :: SChar) a where Source #

Typeclass associating format types (d, f, etc.) with the types that can be formatted by them.

You can extend the printf methods here for your own types by writing your instances here.

Minimal complete definition

Nothing

Methods

formatArg :: p t -> a -> FieldFormat -> ShowS Source #

default formatArg :: PrintfArg a => p t -> a -> FieldFormat -> ShowS Source #

Instances

Instances details
FormatType "E" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "E" -> Double -> FieldFormat -> ShowS Source #

FormatType "E" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "E" -> Float -> FieldFormat -> ShowS Source #

FormatType "F" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "F" -> Double -> FieldFormat -> ShowS Source #

FormatType "F" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "F" -> Float -> FieldFormat -> ShowS Source #

FormatType "G" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "G" -> Double -> FieldFormat -> ShowS Source #

FormatType "G" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "G" -> Float -> FieldFormat -> ShowS Source #

FormatType "X" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Char -> FieldFormat -> ShowS Source #

FormatType "X" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Int -> FieldFormat -> ShowS Source #

FormatType "X" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "X" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "X" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "X" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "X" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Integer -> FieldFormat -> ShowS Source #

FormatType "X" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Natural -> FieldFormat -> ShowS Source #

FormatType "X" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Word -> FieldFormat -> ShowS Source #

FormatType "X" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "X" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "X" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "X" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "X" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "b" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Char -> FieldFormat -> ShowS Source #

FormatType "b" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Int -> FieldFormat -> ShowS Source #

FormatType "b" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "b" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "b" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "b" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "b" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Integer -> FieldFormat -> ShowS Source #

FormatType "b" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Natural -> FieldFormat -> ShowS Source #

FormatType "b" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Word -> FieldFormat -> ShowS Source #

FormatType "b" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "b" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "b" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "b" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "b" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "c" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "c" -> Char -> FieldFormat -> ShowS Source #

FormatType "c" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "c" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "c" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "c" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "d" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Char -> FieldFormat -> ShowS Source #

FormatType "d" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Int -> FieldFormat -> ShowS Source #

FormatType "d" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "d" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "d" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "d" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "d" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Integer -> FieldFormat -> ShowS Source #

FormatType "d" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Natural -> FieldFormat -> ShowS Source #

FormatType "d" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Word -> FieldFormat -> ShowS Source #

FormatType "d" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "d" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "d" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "d" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "d" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "e" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "e" -> Double -> FieldFormat -> ShowS Source #

FormatType "e" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "e" -> Float -> FieldFormat -> ShowS Source #

FormatType "f" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "f" -> Double -> FieldFormat -> ShowS Source #

FormatType "f" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "f" -> Float -> FieldFormat -> ShowS Source #

FormatType "g" Double Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "g" -> Double -> FieldFormat -> ShowS Source #

FormatType "g" Float Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "g" -> Float -> FieldFormat -> ShowS Source #

FormatType "o" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Char -> FieldFormat -> ShowS Source #

FormatType "o" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Int -> FieldFormat -> ShowS Source #

FormatType "o" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "o" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "o" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "o" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "o" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Integer -> FieldFormat -> ShowS Source #

FormatType "o" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Natural -> FieldFormat -> ShowS Source #

FormatType "o" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Word -> FieldFormat -> ShowS Source #

FormatType "o" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "o" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "o" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "o" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "o" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "s" String Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "s" -> String -> FieldFormat -> ShowS Source #

FormatType "s" Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "s" -> Text -> FieldFormat -> ShowS Source #

FormatType "s" Text Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "s" -> Text -> FieldFormat -> ShowS Source #

FormatType "u" Char Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Char -> FieldFormat -> ShowS Source #

FormatType "u" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Int -> FieldFormat -> ShowS Source #

FormatType "u" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "u" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "u" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "u" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "u" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Integer -> FieldFormat -> ShowS Source #

FormatType "u" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Natural -> FieldFormat -> ShowS Source #

FormatType "u" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Word -> FieldFormat -> ShowS Source #

FormatType "u" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "u" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "u" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "u" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "u" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "v" Char Source #

Treats as c

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Char -> FieldFormat -> ShowS Source #

FormatType "v" Double Source #

Treats as g

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Double -> FieldFormat -> ShowS Source #

FormatType "v" Float Source #

Treats as g

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Float -> FieldFormat -> ShowS Source #

FormatType "v" Int Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Int -> FieldFormat -> ShowS Source #

FormatType "v" Int8 Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "v" Int16 Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "v" Int32 Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "v" Int64 Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "v" Integer Source #

Treats as d

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Integer -> FieldFormat -> ShowS Source #

FormatType "v" Natural Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Natural -> FieldFormat -> ShowS Source #

FormatType "v" Word Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Word -> FieldFormat -> ShowS Source #

FormatType "v" Word8 Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "v" Word16 Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "v" Word32 Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "v" Word64 Source #

Treats as u

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Word64 -> FieldFormat -> ShowS Source #

FormatType "v" String Source #

Treats as s

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> String -> FieldFormat -> ShowS Source #

FormatType "v" Text Source #

Treats as s

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Text -> FieldFormat -> ShowS Source #

FormatType "v" Text Source #

Treats as s

Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "v" -> Text -> FieldFormat -> ShowS Source #

FormatType "x" Int Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Int -> FieldFormat -> ShowS Source #

FormatType "x" Int8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Int8 -> FieldFormat -> ShowS Source #

FormatType "x" Int16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Int16 -> FieldFormat -> ShowS Source #

FormatType "x" Int32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Int32 -> FieldFormat -> ShowS Source #

FormatType "x" Int64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Int64 -> FieldFormat -> ShowS Source #

FormatType "x" Integer Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Integer -> FieldFormat -> ShowS Source #

FormatType "x" Natural Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Natural -> FieldFormat -> ShowS Source #

FormatType "x" Word Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Word -> FieldFormat -> ShowS Source #

FormatType "x" Word8 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Word8 -> FieldFormat -> ShowS Source #

FormatType "x" Word16 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Word16 -> FieldFormat -> ShowS Source #

FormatType "x" Word32 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Word32 -> FieldFormat -> ShowS Source #

FormatType "x" Word64 Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatArg :: p "x" -> Word64 -> FieldFormat -> ShowS Source #

type SChar = Symbol Source #

A type synonym for a single-character symbol. Ideally this would just be Char, but we don't have chars at the type level. So, if you see SChar in a type signature, it means that it's expected to be a symbol/string with only one single character.

Single item

pfmt :: forall c a. FormatType c a => PFmt c -> a -> String Source #

Parse and run a single format hole on a single vale. Can be useful for formatting individual items or for testing your own custom instances of FormatType.

Usually meant to be used with OverloadedLabels:

>>> pfmt #f 3.62
"3.62"

However, current versions of GHC disallow labels that aren't valid identifier names, disallowing things like pfmt #.2f 3.62. While there is an <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst approved proposal> that allows this, if you are using an earlier GHC version, you can get around this using mkPFmt:

>>> pfmt (mkPFmt @".2f") 3.6234124
"3.62"

Ideally we'd want to be able to write

>>> pfmt #.2f 3.6234124
"3.62"

(which should be possible in GHC 8.10+)

Note that the format string should not include the leading %.

data PFmt c Source #

Utility type powering pfmt. See documentation for pfmt for more information on usage.

Using OverloadedLabels, you never need to construct this directly can just write #f and a PFmt "f" will be generated. You can also create this using mkPFmt or mkPFmt_, in the situations where OverloadedLabels doesn't work or is not wanted.

Instances

Instances details
(Listify str lst, ff ~ ParseFmt_ lst, Reflect ff, ff ~ 'FF f w p m c) => IsLabel str (PFmt c) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

fromLabel :: PFmt c #

mkPFmt :: forall str lst ff f w q m c. (Listify str lst, ff ~ ParseFmt_ lst, Reflect ff, ff ~ 'FF f w q m c) => PFmt c Source #

Useful for using pfmt without OverloadedLabels, or also when passing format specifiers that aren't currently allowed with OverloadedLabels until GHC 8.10+ (like #.2f).

>>> pfmt (mkPFmt @".2f") 3.6234124
"3.62"

mkPFmt_ :: forall str lst ff f w q m c p. (Listify str lst, ff ~ ParseFmt_ lst, Reflect ff, ff ~ 'FF f w q m c) => p str -> PFmt c Source #

A version of mkPFmt that takes an explicit proxy input.

>>> pfmt (mkPFmt_ (Proxy :: Proxy ".2f")) 3.6234124
"3.62"