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

Description

Internal workings of the printf mechanisms, exposed for potential debugging purposes.

Please do not use this module for anything besides debugging, as is definitely very unstable and might go away or change dramatically between versions.

Synopsis

Documentation

type ParseFmtStr str = EvalParser FmtStrParser str Source #

type ParseFmtStr_ str = EvalParser_ FmtStrParser str Source #

type ParseFmt str = EvalParser FFParser str Source #

type ParseFmt_ str = EvalParser_ FFParser str Source #

data FormatAdjustment #

Whether to left-adjust or zero-pad a field. These are mutually exclusive, with LeftAdjust taking precedence.

Since: base-4.7.0.0

Constructors

LeftAdjust 
ZeroPad 

Instances

Instances details
Reflect 'ZeroPad Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'ZeroPad -> Demote a Source #

Reflect 'LeftAdjust Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'LeftAdjust -> Demote a Source #

type Demote FormatAdjustment Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'ZeroPad Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'ZeroPad = "0"
type ShowFormat 'LeftAdjust Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type family ShowFormat (x :: k) :: Symbol Source #

Instances

Instances details
type ShowFormat (n :: Nat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat (n :: Nat)
type ShowFormat 'ZeroPad Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'ZeroPad = "0"
type ShowFormat 'LeftAdjust Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignSpace Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignSpace = " "
type ShowFormat 'SignPlus Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignPlus = "+"
type ShowFormat 'WMhh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMhh = "hh"
type ShowFormat 'WMh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMh = "h"
type ShowFormat 'WMl Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMl = "l"
type ShowFormat 'WMll Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMll = "ll"
type ShowFormat 'WML Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WML = "L"
type ShowFormat ('Flags a s 'True :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Flags a s 'False :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('FF f w ('Just p) m c :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('FF f w ('Nothing :: Maybe Nat) m c :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Nothing :: Maybe a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Nothing :: Maybe a) = ""
type ShowFormat ('Just x :: Maybe k) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Just x :: Maybe k) = ShowFormat x

data FormatSign #

How to handle the sign of a numeric field. These are mutually exclusive, with SignPlus taking precedence.

Since: base-4.7.0.0

Constructors

SignPlus 
SignSpace 

Instances

Instances details
Reflect 'SignSpace Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'SignSpace -> Demote a Source #

Reflect 'SignPlus Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'SignPlus -> Demote a Source #

type Demote FormatSign Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignSpace Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignSpace = " "
type ShowFormat 'SignPlus Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'SignPlus = "+"

data WidthMod Source #

Constructors

WMhh 
WMh 
WMl 
WMll 
WML 

Instances

Instances details
Reflect 'WMhh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMhh -> Demote a Source #

Reflect 'WMh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMh -> Demote a Source #

Reflect 'WMl Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMl -> Demote a Source #

Reflect 'WMll Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMll -> Demote a Source #

Reflect 'WML Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WML -> Demote a Source #

type Demote WidthMod Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMhh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMhh = "hh"
type ShowFormat 'WMh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMh = "h"
type ShowFormat 'WMl Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMl = "l"
type ShowFormat 'WMll Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WMll = "ll"
type ShowFormat 'WML Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat 'WML = "L"

data Flags Source #

Instances

Instances details
(Reflect d, Reflect i, Reflect l) => Reflect ('Flags d i l :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p ('Flags d i l) -> Demote a Source #

type Demote Flags Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Flags a s 'True :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('Flags a s 'False :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

data FieldFormat Source #

Instances

Instances details
(Reflect flags, Reflect width, Reflect prec, Reflect mods, Reflect chr) => Reflect ('FF flags width prec mods chr :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p ('FF flags width prec mods chr) -> Demote a Source #

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

type Demote FieldFormat Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('FF f w ('Just p) m c :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type ShowFormat ('FF f w ('Nothing :: Maybe Nat) m c :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

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.

type family Demote k = a | a -> k Source #

Instances

Instances details
type Demote Bool Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote Nat Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote Symbol Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote FormatAdjustment Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote FormatSign Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote FieldFormat Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote WidthMod Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote Flags Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote (Maybe a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

type Demote (Maybe a) = Maybe (Demote a)

class Reflect (x :: a) where Source #

Methods

reflect :: p x -> Demote a Source #

Instances

Instances details
Reflect 'False Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'False -> Demote a Source #

Reflect 'True Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'True -> Demote a Source #

KnownNat n => Reflect (n :: Nat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p n -> Demote a Source #

KnownSymbol n => Reflect (n :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p n -> Demote a Source #

Reflect 'ZeroPad Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'ZeroPad -> Demote a Source #

Reflect 'LeftAdjust Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'LeftAdjust -> Demote a Source #

Reflect 'SignSpace Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'SignSpace -> Demote a Source #

Reflect 'SignPlus Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'SignPlus -> Demote a Source #

Reflect 'WMhh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMhh -> Demote a Source #

Reflect 'WMh Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMh -> Demote a Source #

Reflect 'WMl Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMl -> Demote a Source #

Reflect 'WMll Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WMll -> Demote a Source #

Reflect 'WML Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'WML -> Demote a Source #

(Reflect d, Reflect i, Reflect l) => Reflect ('Flags d i l :: Flags) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p ('Flags d i l) -> Demote a Source #

(Reflect flags, Reflect width, Reflect prec, Reflect mods, Reflect chr) => Reflect ('FF flags width prec mods chr :: FieldFormat) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p ('FF flags width prec mods chr) -> Demote a Source #

Reflect ('Nothing :: Maybe a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p 'Nothing -> Demote a0 Source #

Reflect x => Reflect ('Just x :: Maybe a) Source # 
Instance details

Defined in GHC.TypeLits.Printf.Parse

Methods

reflect :: p ('Just x) -> Demote a0 Source #

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 #

class Printf (str :: Symbol) fun where Source #

Methods

printf_ :: 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

Instances

Instances details
(Listify str lst, ffs ~ ParseFmtStr_ lst, FormatFun ffs fun) => Printf str fun Source # 
Instance details

Defined in GHC.TypeLits.Printf.Internal

Methods

printf_ :: p str -> fun Source #

class FormatFun (ffs :: [Either Symbol FieldFormat]) fun where 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.

Methods

formatFun :: p ffs -> String -> fun Source #

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 #

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

Constructors

PFmt FieldFormat 

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 #

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

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"

newtype 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

Constructors

PHelp 

Fields

  • pHelp :: String

    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.

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 #