typelits-printf-0.1.1.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 the variants here will always fail to compile if given arguments of the wrong type (or too many or too little arguments). Most of the variants also provide useful type feedback, 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).

There are three main calling conventions supported:

>>> putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>> putStrLn $ pprintf @"You have %.2f dollars, %s" (PP 3.62) (PP "Luigi")
You have 3.62 dollars, Luigi
>>> putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 :% "Luigi" :% RNil)
You have 3.62 dollars, Luigi

Now comparing their types:

>>> :t printf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatFun '[ .... ] fun => fun
>>> :t pprintf @"You have %.2f dollars, %s" 3.62 "Luigi"
PP "f" -> PP "s" -> String
>>> :t rprintf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatArgs '["f", "s"] -> String
  • The type of printf doesn't tell you immediately what you you need. However, if you do try to use it, the type errors will guide you along the way, iteratively.

    >>> 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.
    
    >>> 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.
    
    >>> printf @"You have %.2f dollars, %s" 3.62 "Luigi"
    You have 3.62 dollars, Luigi
    
    >>> 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.
    
  • For pprintf, it shows you need two arguments: A PP "f" (which is a value that supports being formatted by f) like PP 3.62, and a PP "s", like PP Luigi.
  • rprintf tells you you need a two-item hlist (from Data.Vinyl.Core), where the first item implements f and the second item implements s: 3.62 :% Luigi :% RNil will do.

The following table summarizes the features and drawbacks of each method:

Method True Polyarity Naked Arguments Type feedback
printf Yes Yes Partial (via errors)
pprintf Yes No (requires PP) Yes
rprintf No (HList-based) Yes Yes

Ideally we would have a solution that has all three. However, as of now, we have a "pick two" sort of situation. Suggestions are definitely welcome, however, if you find something that satisfies all three benefits while still allowing for polymorphism!

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

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.

Printf

Unguarded polyarity

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

Type-safe printf with true naked polyarity. 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

While the type of printf @"my fmt string" isn't going to be very helpful, the error messages should help guide you along the way:

>>> 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.
>>> 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.
>>> printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>> 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're having problems getting the error messages to give helpful feedback, try using pHelp:

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

pHelp can give the type system the nudge it needs to provide good errors.

See pprintf for a version of this with nicer types and type errors, but requires wrapping arguments, and rprintf for a version of this with "fake" polyarity, taking a list as input instead. Also see top-level module documentation GHC.TypeLits.Printf for a more comprehensive summary.

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 token 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.

Usually things should work out on their own without needing this ... but sometimes the type system could need a nudge.

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.

Usually things would work out on their own without needing this ... but sometimes the type system could need a nudge.

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. It will come up if you ask for the type of printf, or sometimes if you give the wrong number or type of arguments to it.

>>> :t printf @"You have %.2f dollars, %s"
FormatFun '[ Right ..., 'Left " dollars ", 'Right ...] fun => fun

Every item in the first argument of FormatFun is a chunk of the formatting string, split between format holes (Right) and string chunks (Left). You can successively "eliminate" them by providing more arguments that implement each hole:

>>> :t printf @"You have %.2f dollars, %s" 3.62
FormatFun '[ Right ...] fun => fun

Until you you finally fill all the holes:

>>> :t printf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatFun '[] t => t

at which point you may use it as a String or IO (), in the same way that Text.Printf works. We also support using strict Text lazy Text as well.

So, while it's possible to reason with this using the types, it's usually more difficult than with pprintf and rprintf.

This is why, instead of reasoning with this using its types, it's easier to reason with it using the errors instead:

>>> 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.
>>> 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.
>>> printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>> 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're having problems getting the error messages to give helpful feedback, try using pHelp:

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

pHelp can give the type system the nudge it needs to provide good errors.

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 ~ 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 ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) [a] Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

formatFun :: p '[] -> String -> [a] 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 #

(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 #

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

Defined in GHC.TypeLits.Printf.Internal

Methods

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

Guarded polyarity

pprintf :: forall str ps. (RPrintf str ps, RecordCurry ps) => CurriedF PP ps String Source #

Type-safe printf with true guarded polyarity. Call it like pprintf @"you have %.02f dollars, %s".

A call to printf on a valid string will always give a well-defined type for a function in return:

>>> :t pprintf @"You have %.2f dollars, %s"
PP "f" -> PP "s" -> String

You can always query the type, and get a well-defined type back, which you can utilize using typed holes or other type-guided development techniques.

To give pprintf its arguments, however, they must be wrapped in PP:

>>> putStrLn $ pprintf @"You have %.2f dollars, %s" (PP 3.62) (PP "Luigi")
You have 3.62 dollars, Luigi

See printf for a polyariadic method that doesn't require PP on its inputs, but with a less helpful type signature, and rprintf for a fake-polyariadic method that doesn't require PP, but requires arguments in a single list instead. Also see top-level module documentation GHC.TypeLits.Printf for a more comprehensive summary.

pprintf_ :: forall str ps p. (RPrintf str ps, RecordCurry ps) => p str -> CurriedF PP ps String Source #

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

>>> :t pprintf_ (Proxy :: Proxy "You have %.2f dollars, %s")
PP "f" -> PP "s" -> String

data PP (c :: SChar) Source #

Required wrapper around inputs to pprintf (guarded polyarity). See documentation for pprintf for examples of usage.

You can "wrap" any value in PP as long as it can be formatted as the format type indicated.

For example, to make a PP "f", you can use PP 3.5 or PP 94.2, but not PP (3 :: Int) or PP "hello". To make a value of type PP c, you must wrap a value that can be formatted via c.

Constructors

forall a.FormatType c a => PP a 

List-based polyarity

rprintf :: forall str ps. RPrintf str ps => FormatArgs ps -> String Source #

Type-safe printf with faked polyarity. Pass in a "list" of arguments (using :% and RNil), instead of as multiple arguments. Call it like rprintf @"you have %.02f dollars, %s".

>>> :t rprintf @"You have %.2f dollars, %s"
FormatArgs '["f", "s"] -> String

This means that it is expecting something that can be printed with f and something that can be printed with s. We can provide a Double and a String:

>>> putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 ':%' "Luigi" :% 'RNil')
You have 3.62 dollars, Luigi

See pprintf for a version with true polyarity and good clear types, but requires wrapping its arguments, and printf for a version with true polyarity but less clear types. Also see top-level module documentation GHC.TypeLits.Printf for a more comprehensive summary.

rprintf_ :: RPrintf str ps => p str -> FormatArgs ps -> String Source #

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

>>> :t rprintf_ (Proxy :: Proxy "You have %.2f dollars, %s")
FormatArgs '["f", "s"] -> String

data Rec (a :: u -> Type) (b :: [u]) where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: forall u (a :: u -> Type). Rec a ('[] :: [u]) 

Bundled Patterns

pattern (:%) :: () => FormatType c a => a -> FormatArgs cs -> FormatArgs (c ': cs) infixr 7

Pattern and constructor allowing you to construct a FormatArgs.

To construct a FormatArgs '["f", "s"], for instance, you need to give a value formattable by f and a value formattable by s, given like a linked list, with :% for cons and RNil for nil.

3.62 :% Luigi :% RNil

(This should evoke the idea of of 3.62 : Luigi : [], even though the latter is not possible in Haskell)

Instances

Instances details
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (a :~: b) #

Eq (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f '[] -> Rec f '[] -> Bool #

(/=) :: Rec f '[] -> Rec f '[] -> Bool #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Ord (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f '[] -> Rec f '[] -> Ordering #

(<) :: Rec f '[] -> Rec f '[] -> Bool #

(<=) :: Rec f '[] -> Rec f '[] -> Bool #

(>) :: Rec f '[] -> Rec f '[] -> Bool #

(>=) :: Rec f '[] -> Rec f '[] -> Bool #

max :: Rec f '[] -> Rec f '[] -> Rec f '[] #

min :: Rec f '[] -> Rec f '[] -> Rec f '[] #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Generic (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f '[]) :: Type -> Type #

Methods

from :: Rec f '[] -> Rep (Rec f '[]) x #

to :: Rep (Rec f '[]) x -> Rec f '[] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Semigroup (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f '[] -> Rec f '[] -> Rec f '[] #

sconcat :: NonEmpty (Rec f '[]) -> Rec f '[] #

stimes :: Integral b => b -> Rec f '[] -> Rec f '[] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Monoid (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f '[] #

mappend :: Rec f '[] -> Rec f '[] -> Rec f '[] #

mconcat :: [Rec f '[]] -> Rec f '[] #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Storable (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f '[] -> Int #

alignment :: Rec f '[] -> Int #

peekElemOff :: Ptr (Rec f '[]) -> Int -> IO (Rec f '[]) #

pokeElemOff :: Ptr (Rec f '[]) -> Int -> Rec f '[] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f '[]) #

pokeByteOff :: Ptr b -> Int -> Rec f '[] -> IO () #

peek :: Ptr (Rec f '[]) -> IO (Rec f '[]) #

poke :: Ptr (Rec f '[]) -> Rec f '[] -> IO () #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

type FormatArgs = Rec PP Source #

A heterogeneous list (from Data.Vinyl.Core) used for calling with rprintf. Instead of supplying the inputs as different arguments, we can gather all the inputs into a single list to give to rprintf.

>>> :t rprintf @"You have %.2f dollars, %s"
FormatArgs '["f", "s"] -> String

To construct a FormatArgs '["f", "s"], you need to give a value formattable by f and a value formattable by s, given like a linked list, with :% for cons and RNil for nil.

>>> putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 :% "Luigi" :% RNil)
You have 3.62 dollars, Luigi

(This should evoke the idea of of 3.62 : Luigi : [], even though the latter is not possible in Haskell)

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 does not include the leading %.

data PFmt c Source #

Utility type powering pfmt. See dcumentation 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"