{-# LANGUAGE Safe #-}{-# LANGUAGE TypeOperators #-}{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}------------------------------------------------------------------------------- |-- Module : Text.Printf-- Copyright : (c) Lennart Augustsson and Bart Massey 2013-- License : BSD-style (see the file LICENSE in this distribution)---- Maintainer : Bart Massey <bart@cs.pdx.edu>-- Stability : provisional-- Portability : portable---- A C @printf(3)@-like formatter. This version has been-- extended by Bart Massey as per the recommendations of-- John Meacham and Simon Marlow-- <http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726>-- to support extensible formatting for new datatypes. It-- has also been extended to support almost all C-- @printf(3)@ syntax.-----------------------------------------------------------------------------moduleText.Printf(-- * Printing Functionsprintf ,hPrintf ,-- * Extending To New Types---- | This 'printf' can be extended to format types-- other than those provided for by default. This-- is done by instantiating 'PrintfArg' and providing-- a 'formatArg' for the type. It is possible to-- provide a 'parseFormat' to process type-specific-- modifiers, but the default instance is usually-- the best choice.---- For example:---- > instance PrintfArg () where-- > formatArg x fmt | fmtChar (vFmt 'U' fmt) == 'U' =-- > formatString "()" (fmt { fmtChar = 's', fmtPrecision = Nothing })-- > formatArg _ fmt = errorBadFormat $ fmtChar fmt-- >-- > main :: IO ()-- > main = printf "[%-3.1U]\n" ()---- prints \"@[() ]@\". Note the use of 'formatString' to-- take care of field formatting specifications in a convenient-- way.PrintfArg (..),FieldFormatter ,FieldFormat (..),FormatAdjustment (..),FormatSign (..),vFmt ,-- ** Handling Type-specific Modifiers---- | In the unlikely case that modifier characters of-- some kind are desirable for a user-provided type,-- a 'ModifierParser' can be provided to process these-- characters. The resulting modifiers will appear in-- the 'FieldFormat' for use by the type-specific formatter.ModifierParser ,FormatParse (..),-- ** Standard Formatters---- | These formatters for standard types are provided for-- convenience in writing new type-specific formatters:-- a common pattern is to throw to 'formatString' or-- 'formatInteger' to do most of the format handling for-- a new type.formatString ,formatChar ,formatInt ,formatInteger ,formatRealFloat ,-- ** Raising Errors---- | These functions are used internally to raise various-- errors, and are exported for use by new type-specific-- formatters.errorBadFormat ,errorShortFormat ,errorMissingArgument ,errorBadArgument ,perror ,-- * Implementation Internals-- | These types are needed for implementing processing-- variable numbers of arguments to 'printf' and 'hPrintf'.-- Their implementation is intentionally not visible from-- this module. If you attempt to pass an argument of a type-- which is not an instance of the appropriate class to-- 'printf' or 'hPrintf', then the compiler will report it-- as a missing instance of 'PrintfArg'. (All 'PrintfArg'-- instances are 'PrintfType' instances.)PrintfType ,HPrintfType ,-- | This class is needed as a Haskell98 compatibility-- workaround for the lack of FlexibleInstances.IsChar (..))whereimportData.Char importData.Int importData.List (stripPrefix )importData.Word importNumeric importNumeric.Natural importSystem.IO -- $setup-- >>> import Prelude--------------------- | Format a variable number of arguments with the C-style formatting string.---- >>> printf "%s, %d, %.4f" "hello" 123 pi-- hello, 123, 3.1416---- The return value is either 'String' or @('IO' a)@ (which-- should be @('IO' ())@, but Haskell's type system-- makes this hard).---- The format string consists of ordinary characters and-- /conversion specifications/, which specify how to format-- one of the arguments to 'printf' in the output string. A-- format specification is introduced by the @%@ character;-- this character can be self-escaped into the format string-- using @%%@. A format specification ends with a-- /format character/ that provides the primary information about-- how to format the value. The rest of the conversion-- specification is optional. In order, one may have flag-- characters, a width specifier, a precision specifier, and-- type-specific modifier characters.---- Unlike C @printf(3)@, the formatting of this 'printf'-- is driven by the argument type; formatting is type specific. The-- types formatted by 'printf' \"out of the box\" are:---- * 'Integral' types, including 'Char'---- * 'String'---- * 'RealFloat' types---- 'printf' is also extensible to support other types: see below.---- A conversion specification begins with the-- character @%@, followed by zero or more of the following flags:---- > - left adjust (default is right adjust)-- > + always use a sign (+ or -) for signed conversions-- > space leading space for positive numbers in signed conversions-- > 0 pad with zeros rather than spaces-- > # use an \"alternate form\": see below---- When both flags are given, @-@ overrides @0@ and @+@ overrides space.-- A negative width specifier in a @*@ conversion is treated as-- positive but implies the left adjust flag.---- The \"alternate form\" for unsigned radix conversions is-- as in C @printf(3)@:---- > %o prefix with a leading 0 if needed-- > %x prefix with a leading 0x if nonzero-- > %X prefix with a leading 0X if nonzero-- > %b prefix with a leading 0b if nonzero-- > %[eEfFgG] ensure that the number contains a decimal point---- Any flags are followed optionally by a field width:---- > num field width-- > * as num, but taken from argument list---- The field width is a minimum, not a maximum: it will be-- expanded as needed to avoid mutilating a value.---- Any field width is followed optionally by a precision:---- > .num precision-- > . same as .0-- > .* as num, but taken from argument list---- Negative precision is taken as 0. The meaning of the-- precision depends on the conversion type.---- > Integral minimum number of digits to show-- > RealFloat number of digits after the decimal point-- > String maximum number of characters---- The precision for Integral types is accomplished by zero-padding.-- If both precision and zero-pad are given for an Integral field,-- the zero-pad is ignored.---- Any precision is followed optionally for Integral types-- by a width modifier; the only use of this modifier being-- to set the implicit size of the operand for conversion of-- a negative operand to unsigned:---- > hh Int8-- > h Int16-- > l Int32-- > ll Int64-- > L Int64---- The specification ends with a format character:---- > c character Integral-- > d decimal Integral-- > o octal Integral-- > x hexadecimal Integral-- > X hexadecimal Integral-- > b binary Integral-- > u unsigned decimal Integral-- > f floating point RealFloat-- > F floating point RealFloat-- > g general format float RealFloat-- > G general format float RealFloat-- > e exponent format float RealFloat-- > E exponent format float RealFloat-- > s string String-- > v default format any type---- The \"%v\" specifier is provided for all built-in types,-- and should be provided for user-defined type formatters-- as well. It picks a \"best\" representation for the given-- type. For the built-in types the \"%v\" specifier is-- converted as follows:---- > c Char-- > u other unsigned Integral-- > d other signed Integral-- > g RealFloat-- > s String---- Mismatch between the argument types and the format-- string, as well as any other syntactic or semantic errors-- in the format string, will cause an exception to be-- thrown at runtime.---- Note that the formatting for 'RealFloat' types is-- currently a bit different from that of C @printf(3)@,-- conforming instead to 'Numeric.showEFloat',-- 'Numeric.showFFloat' and 'Numeric.showGFloat' (and their-- alternate versions 'Numeric.showFFloatAlt' and-- 'Numeric.showGFloatAlt'). This is hard to fix: the fixed-- versions would format in a backward-incompatible way.-- In any case the Haskell behavior is generally more-- sensible than the C behavior. A brief summary of some-- key differences:---- * Haskell 'printf' never uses the default \"6-digit\" precision-- used by C printf.---- * Haskell 'printf' treats the \"precision\" specifier as-- indicating the number of digits after the decimal point.---- * Haskell 'printf' prints the exponent of e-format-- numbers without a gratuitous plus sign, and with the-- minimum possible number of digits.---- * Haskell 'printf' will place a zero after a decimal point when-- possible.printf ::(PrintfType r )=>String ->r printf :: forall r. PrintfType r => String -> r printf String fmts =String -> [UPrintf] -> r forall t. PrintfType t => String -> [UPrintf] -> t spr String fmts []-- | Similar to 'printf', except that output is via the specified-- 'Handle'. The return type is restricted to @('IO' a)@.hPrintf ::(HPrintfType r )=>Handle ->String ->r hPrintf :: forall r. HPrintfType r => Handle -> String -> r hPrintf Handle hdl String fmts =Handle -> String -> [UPrintf] -> r forall t. HPrintfType t => Handle -> String -> [UPrintf] -> t hspr Handle hdl String fmts []-- |The 'PrintfType' class provides the variable argument magic for-- 'printf'. Its implementation is intentionally not visible from-- this module. If you attempt to pass an argument of a type which-- is not an instance of this class to 'printf' or 'hPrintf', then-- the compiler will report it as a missing instance of 'PrintfArg'.classPrintfType t wherespr ::String ->[UPrintf ]->t -- | The 'HPrintfType' class provides the variable argument magic for-- 'hPrintf'. Its implementation is intentionally not visible from-- this module.classHPrintfType t wherehspr ::Handle ->String ->[UPrintf ]->t {- not allowed in Haskell 2010 instance PrintfType String where spr fmt args = uprintf fmt (reverse args) -}-- | @since 2.01instance(IsChar c )=>PrintfType [c ]wherespr :: String -> [UPrintf] -> [c] spr String fmts [UPrintf] args =(Char -> c) -> String -> [c] forall a b. (a -> b) -> [a] -> [b] map Char -> c forall c. IsChar c => Char -> c fromChar (String -> [UPrintf] -> String uprintf String fmts ([UPrintf] -> [UPrintf] forall a. [a] -> [a] reverse [UPrintf] args ))-- Note that this should really be (IO ()), but GHC's-- type system won't readily let us say that without-- bringing the GADTs. So we go conditional for these defs.-- | @since 4.7.0.0instance(a ~ ())=>PrintfType (IO a )wherespr :: String -> [UPrintf] -> IO a spr String fmts [UPrintf] args =String -> IO () putStr (String -> IO ()) -> String -> IO () forall a b. (a -> b) -> a -> b $ (Char -> Char) -> String -> String forall a b. (a -> b) -> [a] -> [b] map Char -> Char forall c. IsChar c => Char -> c fromChar (String -> String) -> String -> String forall a b. (a -> b) -> a -> b $ String -> [UPrintf] -> String uprintf String fmts ([UPrintf] -> String) -> [UPrintf] -> String forall a b. (a -> b) -> a -> b $ [UPrintf] -> [UPrintf] forall a. [a] -> [a] reverse [UPrintf] args -- | @since 4.7.0.0instance(a ~ ())=>HPrintfType (IO a )wherehspr :: Handle -> String -> [UPrintf] -> IO a hspr Handle hdl String fmts [UPrintf] args =Handle -> String -> IO () hPutStr Handle hdl (String -> [UPrintf] -> String uprintf String fmts ([UPrintf] -> [UPrintf] forall a. [a] -> [a] reverse [UPrintf] args ))-- | @since 2.01instance(PrintfArg a ,PrintfType r )=>PrintfType (a ->r )wherespr :: String -> [UPrintf] -> a -> r spr String fmts [UPrintf] args =\a a ->String -> [UPrintf] -> r forall t. PrintfType t => String -> [UPrintf] -> t spr String fmts ((a -> ModifierParser forall a. PrintfArg a => a -> ModifierParser parseFormat a a ,a -> FieldFormatter forall a. PrintfArg a => a -> FieldFormatter formatArg a a )UPrintf -> [UPrintf] -> [UPrintf] forall a. a -> [a] -> [a] : [UPrintf] args )-- | @since 2.01instance(PrintfArg a ,HPrintfType r )=>HPrintfType (a ->r )wherehspr :: Handle -> String -> [UPrintf] -> a -> r hspr Handle hdl String fmts [UPrintf] args =\a a ->Handle -> String -> [UPrintf] -> r forall t. HPrintfType t => Handle -> String -> [UPrintf] -> t hspr Handle hdl String fmts ((a -> ModifierParser forall a. PrintfArg a => a -> ModifierParser parseFormat a a ,a -> FieldFormatter forall a. PrintfArg a => a -> FieldFormatter formatArg a a )UPrintf -> [UPrintf] -> [UPrintf] forall a. a -> [a] -> [a] : [UPrintf] args )-- | Typeclass of 'printf'-formattable values. The 'formatArg' method-- takes a value and a field format descriptor and either fails due-- to a bad descriptor or produces a 'ShowS' as the result. The-- default 'parseFormat' expects no modifiers: this is the normal-- case. Minimal instance: 'formatArg'.classPrintfArg a where-- | @since 4.7.0.0formatArg ::a ->FieldFormatter -- | @since 4.7.0.0parseFormat ::a ->ModifierParser parseFormat a _(Char c : String cs )=String -> Char -> ModifierParser FormatParse String ""Char c String cs parseFormat a _String ""=FormatParse forall a. a errorShortFormat -- | @since 2.01instancePrintfArg Char whereformatArg :: Char -> FieldFormatter formatArg =Char -> FieldFormatter formatChar parseFormat :: Char -> ModifierParser parseFormat Char _String cf =Int -> ModifierParser forall a. a -> ModifierParser parseIntFormat (Int forall a. HasCallStack => a undefined ::Int )String cf -- | @since 2.01instance(IsChar c )=>PrintfArg [c ]whereformatArg :: [c] -> FieldFormatter formatArg =[c] -> FieldFormatter forall c. IsChar c => [c] -> FieldFormatter formatString -- | @since 2.01instancePrintfArg Int whereformatArg :: Int -> FieldFormatter formatArg =Int -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Int -> ModifierParser parseFormat =Int -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Int8 whereformatArg :: Int8 -> FieldFormatter formatArg =Int8 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Int8 -> ModifierParser parseFormat =Int8 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Int16 whereformatArg :: Int16 -> FieldFormatter formatArg =Int16 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Int16 -> ModifierParser parseFormat =Int16 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Int32 whereformatArg :: Int32 -> FieldFormatter formatArg =Int32 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Int32 -> ModifierParser parseFormat =Int32 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Int64 whereformatArg :: Int64 -> FieldFormatter formatArg =Int64 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Int64 -> ModifierParser parseFormat =Int64 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Word whereformatArg :: Word -> FieldFormatter formatArg =Word -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Word -> ModifierParser parseFormat =Word -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Word8 whereformatArg :: Word8 -> FieldFormatter formatArg =Word8 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Word8 -> ModifierParser parseFormat =Word8 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Word16 whereformatArg :: Word16 -> FieldFormatter formatArg =Word16 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Word16 -> ModifierParser parseFormat =Word16 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Word32 whereformatArg :: Word32 -> FieldFormatter formatArg =Word32 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Word32 -> ModifierParser parseFormat =Word32 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Word64 whereformatArg :: Word64 -> FieldFormatter formatArg =Word64 -> FieldFormatter forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt parseFormat :: Word64 -> ModifierParser parseFormat =Word64 -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Integer whereformatArg :: Integer -> FieldFormatter formatArg =Integer -> FieldFormatter formatInteger parseFormat :: Integer -> ModifierParser parseFormat =Integer -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 4.8.0.0instancePrintfArg Natural whereformatArg :: Natural -> FieldFormatter formatArg =Integer -> FieldFormatter formatInteger (Integer -> FieldFormatter) -> (Natural -> Integer) -> Natural -> FieldFormatter forall b c a. (b -> c) -> (a -> b) -> a -> c . Natural -> Integer forall a. Integral a => a -> Integer toInteger parseFormat :: Natural -> ModifierParser parseFormat =Natural -> ModifierParser forall a. a -> ModifierParser parseIntFormat -- | @since 2.01instancePrintfArg Float whereformatArg :: Float -> FieldFormatter formatArg =Float -> FieldFormatter forall a. RealFloat a => a -> FieldFormatter formatRealFloat -- | @since 2.01instancePrintfArg Double whereformatArg :: Double -> FieldFormatter formatArg =Double -> FieldFormatter forall a. RealFloat a => a -> FieldFormatter formatRealFloat -- | This class, with only the one instance, is used as-- a workaround for the fact that 'String', as a concrete-- type, is not allowable as a typeclass instance. 'IsChar'-- is exported for backward-compatibility.classIsChar c where-- | @since 4.7.0.0toChar ::c ->Char -- | @since 4.7.0.0fromChar ::Char ->c -- | @since 2.01instanceIsChar Char wheretoChar :: Char -> Char toChar Char c =Char c fromChar :: Char -> Char fromChar Char c =Char c --------------------- | Whether to left-adjust or zero-pad a field. These are-- mutually exclusive, with 'LeftAdjust' taking precedence.---- @since 4.7.0.0dataFormatAdjustment =LeftAdjust |ZeroPad -- | How to handle the sign of a numeric field. These are-- mutually exclusive, with 'SignPlus' taking precedence.---- @since 4.7.0.0dataFormatSign =SignPlus |SignSpace -- | Description of field formatting for 'formatArg'. See UNIX @printf(3)@-- for a description of how field formatting works.---- @since 4.7.0.0dataFieldFormat =FieldFormat {FieldFormat -> Maybe Int fmtWidth ::Maybe Int ,-- ^ Total width of the field.FieldFormat -> Maybe Int fmtPrecision ::Maybe Int ,-- ^ Secondary field width specifier.FieldFormat -> Maybe FormatAdjustment fmtAdjust ::Maybe FormatAdjustment ,-- ^ Kind of filling or padding-- to be done.FieldFormat -> Maybe FormatSign fmtSign ::Maybe FormatSign ,-- ^ Whether to insist on a-- plus sign for positive-- numbers.FieldFormat -> Bool fmtAlternate ::Bool ,-- ^ Indicates an "alternate-- format". See @printf(3)@-- for the details, which-- vary by argument spec.FieldFormat -> String fmtModifiers ::String ,-- ^ Characters that appeared-- immediately to the left of-- 'fmtChar' in the format-- and were accepted by the-- type's 'parseFormat'.-- Normally the empty string.FieldFormat -> Char fmtChar ::Char -- ^ The format character-- 'printf' was invoked-- with. 'formatArg' should-- fail unless this character-- matches the type. It is-- normal to handle many-- different format-- characters for a single-- type.}-- | The \"format parser\" walks over argument-type-specific-- modifier characters to find the primary format character.-- This is the type of its result.---- @since 4.7.0.0dataFormatParse =FormatParse {FormatParse -> String fpModifiers ::String ,-- ^ Any modifiers found.FormatParse -> Char fpChar ::Char ,-- ^ Primary format character.FormatParse -> String fpRest ::String -- ^ Rest of the format string.}-- Contains the "modifier letters" that can precede an-- integer type.intModifierMap ::[(String ,Integer )]intModifierMap :: [(String, Integer)] intModifierMap =[(String "hh",Int8 -> Integer forall a. Integral a => a -> Integer toInteger (Int8 forall a. Bounded a => a minBound ::Int8 )),(String "h",Int16 -> Integer forall a. Integral a => a -> Integer toInteger (Int16 forall a. Bounded a => a minBound ::Int16 )),(String "l",Int32 -> Integer forall a. Integral a => a -> Integer toInteger (Int32 forall a. Bounded a => a minBound ::Int32 )),(String "ll",Int64 -> Integer forall a. Integral a => a -> Integer toInteger (Int64 forall a. Bounded a => a minBound ::Int64 )),(String "L",Int64 -> Integer forall a. Integral a => a -> Integer toInteger (Int64 forall a. Bounded a => a minBound ::Int64 ))]parseIntFormat ::a ->String ->FormatParse parseIntFormat :: forall a. a -> ModifierParser parseIntFormat a _String s =case((String, Integer) -> Maybe FormatParse -> Maybe FormatParse) -> Maybe FormatParse -> [(String, Integer)] -> Maybe FormatParse forall a b. (a -> b -> b) -> b -> [a] -> b forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b foldr (String, Integer) -> Maybe FormatParse -> Maybe FormatParse forall {b}. (String, b) -> Maybe FormatParse -> Maybe FormatParse matchPrefix Maybe FormatParse forall a. Maybe a Nothing [(String, Integer)] intModifierMap ofJust FormatParse m ->FormatParse m Maybe FormatParse Nothing ->caseString s ofChar c : String cs ->String -> Char -> ModifierParser FormatParse String ""Char c String cs String ""->FormatParse forall a. a errorShortFormat wherematchPrefix :: (String, b) -> Maybe FormatParse -> Maybe FormatParse matchPrefix (String p ,b _)m :: Maybe FormatParse m @(Just (FormatParse String p0 Char _String _))|String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length String p0 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length String p =Maybe FormatParse m |Bool otherwise =caseString -> Maybe FormatParse getFormat String p ofMaybe FormatParse Nothing ->Maybe FormatParse m Just FormatParse fp ->FormatParse -> Maybe FormatParse forall a. a -> Maybe a Just FormatParse fp matchPrefix (String p ,b _)Maybe FormatParse Nothing =String -> Maybe FormatParse getFormat String p getFormat :: String -> Maybe FormatParse getFormat String p =String -> String -> Maybe String forall a. Eq a => [a] -> [a] -> Maybe [a] stripPrefix String p String s Maybe String -> (String -> Maybe FormatParse) -> Maybe FormatParse forall a b. Maybe a -> (a -> Maybe b) -> Maybe b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= String -> Maybe FormatParse fp wherefp :: String -> Maybe FormatParse fp (Char c : String cs )=FormatParse -> Maybe FormatParse forall a. a -> Maybe a Just (FormatParse -> Maybe FormatParse) -> FormatParse -> Maybe FormatParse forall a b. (a -> b) -> a -> b $ String -> Char -> ModifierParser FormatParse String p Char c String cs fp String ""=Maybe FormatParse forall a. a errorShortFormat -- | This is the type of a field formatter reified over its-- argument.---- @since 4.7.0.0typeFieldFormatter =FieldFormat ->ShowS -- | Type of a function that will parse modifier characters-- from the format string.---- @since 4.7.0.0typeModifierParser =String ->FormatParse -- | Substitute a \'v\' format character with the given-- default format character in the 'FieldFormat'. A-- convenience for user-implemented types, which should-- support \"%v\".---- @since 4.7.0.0vFmt ::Char ->FieldFormat ->FieldFormat vFmt :: Char -> FieldFormat -> FieldFormat vFmt Char c ufmt :: FieldFormat ufmt @(FieldFormat {fmtChar :: FieldFormat -> Char fmtChar =Char 'v'})=FieldFormat ufmt {fmtChar =c }vFmt Char _FieldFormat ufmt =FieldFormat ufmt -- | Formatter for 'Char' values.---- @since 4.7.0.0formatChar ::Char ->FieldFormatter formatChar :: Char -> FieldFormatter formatChar Char x FieldFormat ufmt =Maybe Integer -> Integer -> FieldFormatter formatIntegral (Integer -> Maybe Integer forall a. a -> Maybe a Just Integer 0)(Int -> Integer forall a. Integral a => a -> Integer toInteger (Int -> Integer) -> Int -> Integer forall a b. (a -> b) -> a -> b $ Char -> Int ord Char x )FieldFormatter -> FieldFormatter forall a b. (a -> b) -> a -> b $ Char -> FieldFormat -> FieldFormat vFmt Char 'c'FieldFormat ufmt -- | Formatter for 'String' values.---- @since 4.7.0.0formatString ::IsChar a =>[a ]->FieldFormatter formatString :: forall c. IsChar c => [c] -> FieldFormatter formatString [a] x FieldFormat ufmt =caseFieldFormat -> Char fmtChar (FieldFormat -> Char) -> FieldFormat -> Char forall a b. (a -> b) -> a -> b $ Char -> FieldFormat -> FieldFormat vFmt Char 's'FieldFormat ufmt ofChar 's'->(Char -> Char) -> String -> String forall a b. (a -> b) -> [a] -> [b] map Char -> Char forall c. IsChar c => c -> Char toChar (String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . (FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (String "",String ts )String -> String -> String forall a. [a] -> [a] -> [a] ++ )wherets :: String ts =(a -> Char) -> [a] -> String forall a b. (a -> b) -> [a] -> [b] map a -> Char forall c. IsChar c => c -> Char toChar ([a] -> String) -> [a] -> String forall a b. (a -> b) -> a -> b $ Maybe Int -> [a] trunc (Maybe Int -> [a]) -> Maybe Int -> [a] forall a b. (a -> b) -> a -> b $ FieldFormat -> Maybe Int fmtPrecision FieldFormat ufmt wheretrunc :: Maybe Int -> [a] trunc Maybe Int Nothing =[a] x trunc (Just Int n )=Int -> [a] -> [a] forall a. Int -> [a] -> [a] take Int n [a] x Char c ->Char -> String -> String forall a. Char -> a errorBadFormat Char c -- Possibly apply the int modifiers to get a new-- int width for conversion.fixupMods ::FieldFormat ->Maybe Integer ->Maybe Integer fixupMods :: FieldFormat -> Maybe Integer -> Maybe Integer fixupMods FieldFormat ufmt Maybe Integer m =letmods :: String mods =FieldFormat -> String fmtModifiers FieldFormat ufmt incaseString mods ofString ""->Maybe Integer m String _->caseString -> [(String, Integer)] -> Maybe Integer forall a b. Eq a => a -> [(a, b)] -> Maybe b lookup String mods [(String, Integer)] intModifierMap ofJust Integer m0 ->Integer -> Maybe Integer forall a. a -> Maybe a Just Integer m0 Maybe Integer Nothing ->String -> Maybe Integer forall a. String -> a perror String "unknown format modifier"-- | Formatter for 'Int' values.---- @since 4.7.0.0formatInt ::(Integral a ,Bounded a )=>a ->FieldFormatter formatInt :: forall a. (Integral a, Bounded a) => a -> FieldFormatter formatInt a x FieldFormat ufmt =letlb :: Integer lb =a -> Integer forall a. Integral a => a -> Integer toInteger (a -> Integer) -> a -> Integer forall a b. (a -> b) -> a -> b $ a forall a. Bounded a => a minBound a -> a -> a forall a. a -> a -> a `asTypeOf` a x m :: Maybe Integer m =FieldFormat -> Maybe Integer -> Maybe Integer fixupMods FieldFormat ufmt (Integer -> Maybe Integer forall a. a -> Maybe a Just Integer lb )ufmt' :: FieldFormat ufmt' =caseInteger lb ofInteger 0->Char -> FieldFormat -> FieldFormat vFmt Char 'u'FieldFormat ufmt Integer _->FieldFormat ufmt inMaybe Integer -> Integer -> FieldFormatter formatIntegral Maybe Integer m (a -> Integer forall a. Integral a => a -> Integer toInteger a x )FieldFormat ufmt' -- | Formatter for 'Integer' values.---- @since 4.7.0.0formatInteger ::Integer ->FieldFormatter formatInteger :: Integer -> FieldFormatter formatInteger Integer x FieldFormat ufmt =letm :: Maybe Integer m =FieldFormat -> Maybe Integer -> Maybe Integer fixupMods FieldFormat ufmt Maybe Integer forall a. Maybe a Nothing inMaybe Integer -> Integer -> FieldFormatter formatIntegral Maybe Integer m Integer x FieldFormat ufmt -- All formatting for integral types is handled-- consistently. The only difference is between Integer and-- bounded types; this difference is handled by the 'm'-- argument containing the lower bound.formatIntegral ::Maybe Integer ->Integer ->FieldFormatter formatIntegral :: Maybe Integer -> Integer -> FieldFormatter formatIntegral Maybe Integer m Integer x FieldFormat ufmt0 =letprec :: Maybe Int prec =FieldFormat -> Maybe Int fmtPrecision FieldFormat ufmt0 incaseFieldFormat -> Char fmtChar FieldFormat ufmt ofChar 'd'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Maybe Int -> Integer -> (String, String) fmti Maybe Int prec Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'i'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Maybe Int -> Integer -> (String, String) fmti Maybe Int prec Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'x'->(FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer 16(String -> Integer -> Maybe String forall {a} {a}. (Eq a, Num a) => a -> a -> Maybe a alt String "0x"Integer x )Maybe Int prec Maybe Integer m Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'X'->(FieldFormat -> (String, String) -> String adjust FieldFormat ufmt ((String, String) -> (String, String) forall {a}. (a, String) -> (a, String) upcase ((String, String) -> (String, String)) -> (String, String) -> (String, String) forall a b. (a -> b) -> a -> b $ Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer 16(String -> Integer -> Maybe String forall {a} {a}. (Eq a, Num a) => a -> a -> Maybe a alt String "0X"Integer x )Maybe Int prec Maybe Integer m Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'b'->(FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer 2(String -> Integer -> Maybe String forall {a} {a}. (Eq a, Num a) => a -> a -> Maybe a alt String "0b"Integer x )Maybe Int prec Maybe Integer m Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'o'->(FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer 8(String -> Integer -> Maybe String forall {a} {a}. (Eq a, Num a) => a -> a -> Maybe a alt String "0"Integer x )Maybe Int prec Maybe Integer m Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'u'->(FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer 10Maybe String forall a. Maybe a Nothing Maybe Int prec Maybe Integer m Integer x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'c'|Integer x Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool >= Int -> Integer forall a b. (Integral a, Num b) => a -> b fromIntegral (Char -> Int ord (Char forall a. Bounded a => a minBound ::Char ))Bool -> Bool -> Bool && Integer x Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool <= Int -> Integer forall a b. (Integral a, Num b) => a -> b fromIntegral (Char -> Int ord (Char forall a. Bounded a => a maxBound ::Char ))Bool -> Bool -> Bool && FieldFormat -> Maybe Int fmtPrecision FieldFormat ufmt Maybe Int -> Maybe Int -> Bool forall a. Eq a => a -> a -> Bool == Maybe Int forall a. Maybe a Nothing Bool -> Bool -> Bool && FieldFormat -> String fmtModifiers FieldFormat ufmt String -> String -> Bool forall a. Eq a => a -> a -> Bool == String ""->String -> FieldFormatter forall c. IsChar c => [c] -> FieldFormatter formatString [Int -> Char chr (Int -> Char) -> Int -> Char forall a b. (a -> b) -> a -> b $ Integer -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Integer x ](FieldFormat ufmt {fmtChar ='s'})Char 'c'->String -> String -> String forall a. String -> a perror String "illegal char conversion"Char c ->Char -> String -> String forall a. Char -> a errorBadFormat Char c whereufmt :: FieldFormat ufmt =Char -> FieldFormat -> FieldFormat vFmt Char 'd'(FieldFormat -> FieldFormat) -> FieldFormat -> FieldFormat forall a b. (a -> b) -> a -> b $ caseFieldFormat ufmt0 ofFieldFormat {fmtPrecision :: FieldFormat -> Maybe Int fmtPrecision =Just Int _,fmtAdjust :: FieldFormat -> Maybe FormatAdjustment fmtAdjust =Just FormatAdjustment ZeroPad }->FieldFormat ufmt0 {fmtAdjust =Nothing }FieldFormat _->FieldFormat ufmt0 alt :: a -> a -> Maybe a alt a _a 0=Maybe a forall a. Maybe a Nothing alt a p a _=caseFieldFormat -> Bool fmtAlternate FieldFormat ufmt ofBool True ->a -> Maybe a forall a. a -> Maybe a Just a p Bool False ->Maybe a forall a. Maybe a Nothing upcase :: (a, String) -> (a, String) upcase (a s1 ,String s2 )=(a s1 ,(Char -> Char) -> String -> String forall a b. (a -> b) -> [a] -> [b] map Char -> Char toUpper String s2 )-- | Formatter for 'RealFloat' values.---- @since 4.7.0.0formatRealFloat ::RealFloat a =>a ->FieldFormatter formatRealFloat :: forall a. RealFloat a => a -> FieldFormatter formatRealFloat a x FieldFormat ufmt =letc :: Char c =FieldFormat -> Char fmtChar (FieldFormat -> Char) -> FieldFormat -> Char forall a b. (a -> b) -> a -> b $ Char -> FieldFormat -> FieldFormat vFmt Char 'g'FieldFormat ufmt prec :: Maybe Int prec =FieldFormat -> Maybe Int fmtPrecision FieldFormat ufmt alt :: Bool alt =FieldFormat -> Bool fmtAlternate FieldFormat ufmt incaseChar c ofChar 'e'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'E'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'f'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'F'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'g'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char 'G'->(FieldFormat -> (String, String) -> String adjustSigned FieldFormat ufmt (Char -> Maybe Int -> Bool -> a -> (String, String) forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int prec Bool alt a x )String -> String -> String forall a. [a] -> [a] -> [a] ++ )Char _->Char -> String -> String forall a. Char -> a errorBadFormat Char c -- This is the type carried around for arguments in-- the varargs code.typeUPrintf =(ModifierParser ,FieldFormatter )-- Given a format string and a list of formatting functions-- (the actual argument value having already been baked into-- each of these functions before delivery), return the-- actual formatted text string.uprintf ::String ->[UPrintf ]->String uprintf :: String -> [UPrintf] -> String uprintf String s [UPrintf] us =String -> [UPrintf] -> String -> String uprintfs String s [UPrintf] us String ""-- This function does the actual work, producing a ShowS-- instead of a string, for future expansion and for-- misguided efficiency.uprintfs ::String ->[UPrintf ]->ShowS uprintfs :: String -> [UPrintf] -> String -> String uprintfs String ""[]=String -> String forall a. a -> a id uprintfs String ""(UPrintf _: [UPrintf] _)=String -> String forall a. a errorShortFormat uprintfs (Char '%': Char '%': String cs )[UPrintf] us =(Char '%'Char -> String -> String forall a. a -> [a] -> [a] : )(String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> [UPrintf] -> String -> String uprintfs String cs [UPrintf] us uprintfs (Char '%': String _)[]=String -> String forall a. a errorMissingArgument uprintfs (Char '%': String cs )us :: [UPrintf] us @(UPrintf _: [UPrintf] _)=String -> [UPrintf] -> String -> String fmt String cs [UPrintf] us uprintfs (Char c : String cs )[UPrintf] us =(Char c Char -> String -> String forall a. a -> [a] -> [a] : )(String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> [UPrintf] -> String -> String uprintfs String cs [UPrintf] us -- Given a suffix of the format string starting just after-- the percent sign, and the list of remaining unprocessed-- arguments in the form described above, format the portion-- of the output described by this field description, and-- then continue with 'uprintfs'.fmt ::String ->[UPrintf ]->ShowS fmt :: String -> [UPrintf] -> String -> String fmt String cs0 [UPrintf] us0 =caseBool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool False Bool False Maybe FormatSign forall a. Maybe a Nothing Bool False String cs0 [UPrintf] us0 of(FieldFormat _,String _,[])->String -> String forall a. a errorMissingArgument (FieldFormat ufmt ,String cs ,(ModifierParser _,FieldFormatter u ): [UPrintf] us )->FieldFormatter u FieldFormat ufmt (String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> [UPrintf] -> String -> String uprintfs String cs [UPrintf] us -- Given field formatting information, and a tuple-- consisting of a prefix (for example, a minus sign) that-- is supposed to go before the argument value and a string-- representing the value, return the properly padded and-- formatted result.adjust ::FieldFormat ->(String ,String )->String adjust :: FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (String pre ,String str )=letnaturalWidth :: Int naturalWidth =String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length String pre Int -> Int -> Int forall a. Num a => a -> a -> a + String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length String str zero :: Bool zero =caseFieldFormat -> Maybe FormatAdjustment fmtAdjust FieldFormat ufmt ofJust FormatAdjustment ZeroPad ->Bool True Maybe FormatAdjustment _->Bool False left :: Bool left =caseFieldFormat -> Maybe FormatAdjustment fmtAdjust FieldFormat ufmt ofJust FormatAdjustment LeftAdjust ->Bool True Maybe FormatAdjustment _->Bool False fill :: String fill =caseFieldFormat -> Maybe Int fmtWidth FieldFormat ufmt ofJust Int width |Int naturalWidth Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int width ->letfillchar :: Char fillchar =ifBool zero thenChar '0'elseChar ' 'inInt -> Char -> String forall a. Int -> a -> [a] replicate (Int width Int -> Int -> Int forall a. Num a => a -> a -> a - Int naturalWidth )Char fillchar Maybe Int _->String ""inifBool left thenString pre String -> String -> String forall a. [a] -> [a] -> [a] ++ String str String -> String -> String forall a. [a] -> [a] -> [a] ++ String fill elseifBool zero thenString pre String -> String -> String forall a. [a] -> [a] -> [a] ++ String fill String -> String -> String forall a. [a] -> [a] -> [a] ++ String str elseString fill String -> String -> String forall a. [a] -> [a] -> [a] ++ String pre String -> String -> String forall a. [a] -> [a] -> [a] ++ String str -- For positive numbers with an explicit sign field ("+" or-- " "), adjust accordingly.adjustSigned ::FieldFormat ->(String ,String )->String adjustSigned :: FieldFormat -> (String, String) -> String adjustSigned ufmt :: FieldFormat ufmt @(FieldFormat {fmtSign :: FieldFormat -> Maybe FormatSign fmtSign =Just FormatSign SignPlus })(String "",String str )=FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (String "+",String str )adjustSigned ufmt :: FieldFormat ufmt @(FieldFormat {fmtSign :: FieldFormat -> Maybe FormatSign fmtSign =Just FormatSign SignSpace })(String "",String str )=FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (String " ",String str )adjustSigned FieldFormat ufmt (String, String) ps =FieldFormat -> (String, String) -> String adjust FieldFormat ufmt (String, String) ps -- Format a signed integer in the "default" fashion.-- This will be subjected to adjust subsequently.fmti ::Maybe Int ->Integer ->(String ,String )fmti :: Maybe Int -> Integer -> (String, String) fmti Maybe Int prec Integer i |Integer i Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0=(String "-",Maybe Int -> String -> String integral_prec Maybe Int prec (Integer -> String forall a. Show a => a -> String show (-Integer i )))|Bool otherwise =(String "",Maybe Int -> String -> String integral_prec Maybe Int prec (Integer -> String forall a. Show a => a -> String show Integer i ))-- Format an unsigned integer in the "default" fashion.-- This will be subjected to adjust subsequently. The 'b'-- argument is the base, the 'pre' argument is the prefix,-- and the '(Just m)' argument is the implicit lower-bound-- size of the operand for conversion from signed to-- unsigned. Thus, this function will refuse to convert an-- unbounded negative integer to an unsigned string.fmtu ::Integer ->Maybe String ->Maybe Int ->Maybe Integer ->Integer ->(String ,String )fmtu :: Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer b (Just String pre )Maybe Int prec Maybe Integer m Integer i =let(String "",String s )=Integer -> Maybe String -> Maybe Int -> Maybe Integer -> Integer -> (String, String) fmtu Integer b Maybe String forall a. Maybe a Nothing Maybe Int prec Maybe Integer m Integer i incaseString pre ofString "0"->caseString s ofChar '0': String _->(String "",String s )String _->(String pre ,String s )String _->(String pre ,String s )fmtu Integer b Maybe String Nothing Maybe Int prec0 Maybe Integer m0 Integer i0 =caseMaybe Int -> Maybe Integer -> Integer -> Maybe String fmtu' Maybe Int prec0 Maybe Integer m0 Integer i0 ofJust String s ->(String "",String s )Maybe String Nothing ->(String, String) forall a. a errorBadArgument wherefmtu' ::Maybe Int ->Maybe Integer ->Integer ->Maybe String fmtu' :: Maybe Int -> Maybe Integer -> Integer -> Maybe String fmtu' Maybe Int prec (Just Integer m )Integer i |Integer i Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0=Maybe Int -> Maybe Integer -> Integer -> Maybe String fmtu' Maybe Int prec Maybe Integer forall a. Maybe a Nothing (-Integer 2Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer m Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer i )fmtu' (Just Int prec )Maybe Integer _Integer i |Integer i Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool >= Integer 0=(String -> String) -> Maybe String -> Maybe String forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Maybe Int -> String -> String integral_prec (Int -> Maybe Int forall a. a -> Maybe a Just Int prec ))(Maybe String -> Maybe String) -> Maybe String -> Maybe String forall a b. (a -> b) -> a -> b $ Maybe Int -> Maybe Integer -> Integer -> Maybe String fmtu' Maybe Int forall a. Maybe a Nothing Maybe Integer forall a. Maybe a Nothing Integer i fmtu' Maybe Int Nothing Maybe Integer _Integer i |Integer i Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool >= Integer 0=String -> Maybe String forall a. a -> Maybe a Just (String -> Maybe String) -> String -> Maybe String forall a b. (a -> b) -> a -> b $ Integer -> (Int -> Char) -> Integer -> String -> String forall a. Integral a => a -> (Int -> Char) -> a -> String -> String showIntAtBase Integer b Int -> Char intToDigit Integer i String ""fmtu' Maybe Int _Maybe Integer _Integer _=Maybe String forall a. Maybe a Nothing -- This is used by 'fmtu' and 'fmti' to zero-pad an-- int-string to a required precision.integral_prec ::Maybe Int ->String ->String integral_prec :: Maybe Int -> String -> String integral_prec Maybe Int Nothing String integral =String integral integral_prec (Just Int 0)String "0"=String ""integral_prec (Just Int prec )String integral =Int -> Char -> String forall a. Int -> a -> [a] replicate (Int prec Int -> Int -> Int forall a. Num a => a -> a -> a - String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length String integral )Char '0'String -> String -> String forall a. [a] -> [a] -> [a] ++ String integral stoi ::String ->(Int ,String )stoi :: String -> (Int, String) stoi String cs =let(String as ,String cs' )=(Char -> Bool) -> String -> (String, String) forall a. (a -> Bool) -> [a] -> ([a], [a]) span Char -> Bool isDigit String cs incaseString as ofString ""->(Int 0,String cs' )String _->(String -> Int forall a. Read a => String -> a read String as ,String cs' )-- Figure out the FormatAdjustment, given:-- width, precision, left-adjust, zero-filladjustment ::Maybe Int ->Maybe a ->Bool ->Bool ->Maybe FormatAdjustment adjustment :: forall a. Maybe Int -> Maybe a -> Bool -> Bool -> Maybe FormatAdjustment adjustment Maybe Int w Maybe a p Bool l Bool z =caseMaybe Int w ofJust Int n |Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0->Maybe a -> Bool -> Bool -> Maybe FormatAdjustment forall {p}. p -> Bool -> Bool -> Maybe FormatAdjustment adjl Maybe a p Bool True Bool z Maybe Int _->Maybe a -> Bool -> Bool -> Maybe FormatAdjustment forall {p}. p -> Bool -> Bool -> Maybe FormatAdjustment adjl Maybe a p Bool l Bool z whereadjl :: p -> Bool -> Bool -> Maybe FormatAdjustment adjl p _Bool True Bool _=FormatAdjustment -> Maybe FormatAdjustment forall a. a -> Maybe a Just FormatAdjustment LeftAdjust adjl p _Bool False Bool True =FormatAdjustment -> Maybe FormatAdjustment forall a. a -> Maybe a Just FormatAdjustment ZeroPad adjl p _Bool _Bool _=Maybe FormatAdjustment forall a. Maybe a Nothing -- Parse the various format controls to get a format specification.getSpecs ::Bool ->Bool ->Maybe FormatSign ->Bool ->String ->[UPrintf ]->(FieldFormat ,String ,[UPrintf ])getSpecs :: Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool _Bool z Maybe FormatSign s Bool a (Char '-': String cs0 )[UPrintf] us =Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool True Bool z Maybe FormatSign s Bool a String cs0 [UPrintf] us getSpecs Bool l Bool z Maybe FormatSign _Bool a (Char '+': String cs0 )[UPrintf] us =Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool l Bool z (FormatSign -> Maybe FormatSign forall a. a -> Maybe a Just FormatSign SignPlus )Bool a String cs0 [UPrintf] us getSpecs Bool l Bool z Maybe FormatSign s Bool a (Char ' ': String cs0 )[UPrintf] us =Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool l Bool z Maybe FormatSign ss Bool a String cs0 [UPrintf] us wheress :: Maybe FormatSign ss =caseMaybe FormatSign s ofJust FormatSign SignPlus ->FormatSign -> Maybe FormatSign forall a. a -> Maybe a Just FormatSign SignPlus Maybe FormatSign _->FormatSign -> Maybe FormatSign forall a. a -> Maybe a Just FormatSign SignSpace getSpecs Bool l Bool _Maybe FormatSign s Bool a (Char '0': String cs0 )[UPrintf] us =Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool l Bool True Maybe FormatSign s Bool a String cs0 [UPrintf] us getSpecs Bool l Bool z Maybe FormatSign s Bool _(Char '#': String cs0 )[UPrintf] us =Bool -> Bool -> Maybe FormatSign -> Bool -> String -> [UPrintf] -> (FieldFormat, String, [UPrintf]) getSpecs Bool l Bool z Maybe FormatSign s Bool True String cs0 [UPrintf] us getSpecs Bool l Bool z Maybe FormatSign s Bool a (Char '*': String cs0 )[UPrintf] us =let([UPrintf] us' ,Int n )=[UPrintf] -> ([UPrintf], Int) getStar [UPrintf] us ((Maybe Int p ,String cs'' ),[UPrintf] us'' )=caseString cs0 ofChar '.': Char '*': String r ->let([UPrintf] us''' ,Int p' )=[UPrintf] -> ([UPrintf], Int) getStar [UPrintf] us' in((Int -> Maybe Int forall a. a -> Maybe a Just Int p' ,String r ),[UPrintf] us''' )Char '.': String r ->let(Int p' ,String r' )=String -> (Int, String) stoi String r in((Int -> Maybe Int forall a. a -> Maybe a Just Int p' ,String r' ),[UPrintf] us' )String _->((Maybe Int forall a. Maybe a Nothing ,String cs0 ),[UPrintf] us' )FormatParse String ms Char c String cs =case[UPrintf] us'' of(ModifierParser ufmt ,FieldFormatter _): [UPrintf] _->ModifierParser ufmt String cs'' []->FormatParse forall a. a errorMissingArgument in(FieldFormat {fmtWidth :: Maybe Int fmtWidth =Int -> Maybe Int forall a. a -> Maybe a Just (Int -> Int forall a. Num a => a -> a abs Int n ),fmtPrecision :: Maybe Int fmtPrecision =Maybe Int p ,fmtAdjust :: Maybe FormatAdjustment fmtAdjust =Maybe Int -> Maybe Int -> Bool -> Bool -> Maybe FormatAdjustment forall a. Maybe Int -> Maybe a -> Bool -> Bool -> Maybe FormatAdjustment adjustment (Int -> Maybe Int forall a. a -> Maybe a Just Int n )Maybe Int p Bool l Bool z ,fmtSign :: Maybe FormatSign fmtSign =Maybe FormatSign s ,fmtAlternate :: Bool fmtAlternate =Bool a ,fmtModifiers :: String fmtModifiers =String ms ,fmtChar :: Char fmtChar =Char c },String cs ,[UPrintf] us'' )getSpecs Bool l Bool z Maybe FormatSign s Bool a (Char '.': String cs0 )[UPrintf] us =let((Int p ,String cs' ),[UPrintf] us' )=caseString cs0 ofChar '*': String cs'' ->let([UPrintf] us'' ,Int p' )=[UPrintf] -> ([UPrintf], Int) getStar [UPrintf] us in((Int p' ,String cs'' ),[UPrintf] us'' )String _->(String -> (Int, String) stoi String cs0 ,[UPrintf] us )FormatParse String ms Char c String cs =case[UPrintf] us' of(ModifierParser ufmt ,FieldFormatter _): [UPrintf] _->ModifierParser ufmt String cs' []->FormatParse forall a. a errorMissingArgument in(FieldFormat {fmtWidth :: Maybe Int fmtWidth =Maybe Int forall a. Maybe a Nothing ,fmtPrecision :: Maybe Int fmtPrecision =Int -> Maybe Int forall a. a -> Maybe a Just Int p ,fmtAdjust :: Maybe FormatAdjustment fmtAdjust =Maybe Int -> Maybe Int -> Bool -> Bool -> Maybe FormatAdjustment forall a. Maybe Int -> Maybe a -> Bool -> Bool -> Maybe FormatAdjustment adjustment Maybe Int forall a. Maybe a Nothing (Int -> Maybe Int forall a. a -> Maybe a Just Int p )Bool l Bool z ,fmtSign :: Maybe FormatSign fmtSign =Maybe FormatSign s ,fmtAlternate :: Bool fmtAlternate =Bool a ,fmtModifiers :: String fmtModifiers =String ms ,fmtChar :: Char fmtChar =Char c },String cs ,[UPrintf] us' )getSpecs Bool l Bool z Maybe FormatSign s Bool a cs0 :: String cs0 @(Char c0 : String _)[UPrintf] us |Char -> Bool isDigit Char c0 =let(Int n ,String cs' )=String -> (Int, String) stoi String cs0 ((Maybe Int p ,String cs'' ),[UPrintf] us' )=caseString cs' ofChar '.': Char '*': String r ->let([UPrintf] us'' ,Int p' )=[UPrintf] -> ([UPrintf], Int) getStar [UPrintf] us in((Int -> Maybe Int forall a. a -> Maybe a Just Int p' ,String r ),[UPrintf] us'' )Char '.': String r ->let(Int p' ,String r' )=String -> (Int, String) stoi String r in((Int -> Maybe Int forall a. a -> Maybe a Just Int p' ,String r' ),[UPrintf] us )String _->((Maybe Int forall a. Maybe a Nothing ,String cs' ),[UPrintf] us )FormatParse String ms Char c String cs =case[UPrintf] us' of(ModifierParser ufmt ,FieldFormatter _): [UPrintf] _->ModifierParser ufmt String cs'' []->FormatParse forall a. a errorMissingArgument in(FieldFormat {fmtWidth :: Maybe Int fmtWidth =Int -> Maybe Int forall a. a -> Maybe a Just (Int -> Int forall a. Num a => a -> a abs Int n ),fmtPrecision :: Maybe Int fmtPrecision =Maybe Int p ,fmtAdjust :: Maybe FormatAdjustment fmtAdjust =Maybe Int -> Maybe Int -> Bool -> Bool -> Maybe FormatAdjustment forall a. Maybe Int -> Maybe a -> Bool -> Bool -> Maybe FormatAdjustment adjustment (Int -> Maybe Int forall a. a -> Maybe a Just Int n )Maybe Int p Bool l Bool z ,fmtSign :: Maybe FormatSign fmtSign =Maybe FormatSign s ,fmtAlternate :: Bool fmtAlternate =Bool a ,fmtModifiers :: String fmtModifiers =String ms ,fmtChar :: Char fmtChar =Char c },String cs ,[UPrintf] us' )getSpecs Bool l Bool z Maybe FormatSign s Bool a cs0 :: String cs0 @(Char _: String _)[UPrintf] us =letFormatParse String ms Char c String cs =case[UPrintf] us of(ModifierParser ufmt ,FieldFormatter _): [UPrintf] _->ModifierParser ufmt String cs0 []->FormatParse forall a. a errorMissingArgument in(FieldFormat {fmtWidth :: Maybe Int fmtWidth =Maybe Int forall a. Maybe a Nothing ,fmtPrecision :: Maybe Int fmtPrecision =Maybe Int forall a. Maybe a Nothing ,fmtAdjust :: Maybe FormatAdjustment fmtAdjust =Maybe Int -> Maybe Any -> Bool -> Bool -> Maybe FormatAdjustment forall a. Maybe Int -> Maybe a -> Bool -> Bool -> Maybe FormatAdjustment adjustment Maybe Int forall a. Maybe a Nothing Maybe Any forall a. Maybe a Nothing Bool l Bool z ,fmtSign :: Maybe FormatSign fmtSign =Maybe FormatSign s ,fmtAlternate :: Bool fmtAlternate =Bool a ,fmtModifiers :: String fmtModifiers =String ms ,fmtChar :: Char fmtChar =Char c },String cs ,[UPrintf] us )getSpecs Bool _Bool _Maybe FormatSign _Bool _String ""[UPrintf] _=(FieldFormat, String, [UPrintf]) forall a. a errorShortFormat -- Process a star argument in a format specification.getStar ::[UPrintf ]->([UPrintf ],Int )getStar :: [UPrintf] -> ([UPrintf], Int) getStar [UPrintf] us =letufmt :: FieldFormat ufmt =FieldFormat {fmtWidth :: Maybe Int fmtWidth =Maybe Int forall a. Maybe a Nothing ,fmtPrecision :: Maybe Int fmtPrecision =Maybe Int forall a. Maybe a Nothing ,fmtAdjust :: Maybe FormatAdjustment fmtAdjust =Maybe FormatAdjustment forall a. Maybe a Nothing ,fmtSign :: Maybe FormatSign fmtSign =Maybe FormatSign forall a. Maybe a Nothing ,fmtAlternate :: Bool fmtAlternate =Bool False ,fmtModifiers :: String fmtModifiers =String "",fmtChar :: Char fmtChar =Char 'd'}incase[UPrintf] us of[]->([UPrintf], Int) forall a. a errorMissingArgument (ModifierParser _,FieldFormatter nu ): [UPrintf] us' ->([UPrintf] us' ,String -> Int forall a. Read a => String -> a read (FieldFormatter nu FieldFormat ufmt String ""))-- Format a RealFloat value.dfmt ::(RealFloat a )=>Char ->Maybe Int ->Bool ->a ->(String ,String )dfmt :: forall a. RealFloat a => Char -> Maybe Int -> Bool -> a -> (String, String) dfmt Char c Maybe Int p Bool a a d =letcaseConvert :: String -> String caseConvert =ifChar -> Bool isUpper Char c then(Char -> Char) -> String -> String forall a b. (a -> b) -> [a] -> [b] map Char -> Char toUpper elseString -> String forall a. a -> a id showFunction :: Maybe Int -> a -> String -> String showFunction =caseChar -> Char toLower Char c ofChar 'e'->Maybe Int -> a -> String -> String forall a. RealFloat a => Maybe Int -> a -> String -> String showEFloat Char 'f'->ifBool a thenMaybe Int -> a -> String -> String forall a. RealFloat a => Maybe Int -> a -> String -> String showFFloatAlt elseMaybe Int -> a -> String -> String forall a. RealFloat a => Maybe Int -> a -> String -> String showFFloat Char 'g'->ifBool a thenMaybe Int -> a -> String -> String forall a. RealFloat a => Maybe Int -> a -> String -> String showGFloatAlt elseMaybe Int -> a -> String -> String forall a. RealFloat a => Maybe Int -> a -> String -> String showGFloat Char _->String -> Maybe Int -> a -> String -> String forall a. String -> a perror String "internal error: impossible dfmt"result :: String result =String -> String caseConvert (String -> String) -> String -> String forall a b. (a -> b) -> a -> b $ Maybe Int -> a -> String -> String showFunction Maybe Int p a d String ""incaseString result ofChar '-': String cs ->(String "-",String cs )String cs ->(String "",String cs )-- | Raises an 'error' with a printf-specific prefix on the-- message string.---- @since 4.7.0.0perror ::String ->a perror :: forall a. String -> a perror String s =String -> a forall a. String -> a errorWithoutStackTrace (String -> a) -> String -> a forall a b. (a -> b) -> a -> b $ String "printf: "String -> String -> String forall a. [a] -> [a] -> [a] ++ String s -- | Calls 'perror' to indicate an unknown format letter for-- a given type.---- @since 4.7.0.0errorBadFormat ::Char ->a errorBadFormat :: forall a. Char -> a errorBadFormat Char c =String -> a forall a. String -> a perror (String -> a) -> String -> a forall a b. (a -> b) -> a -> b $ String "bad formatting char "String -> String -> String forall a. [a] -> [a] -> [a] ++ Char -> String forall a. Show a => a -> String show Char c errorShortFormat ,errorMissingArgument ,errorBadArgument ::a -- | Calls 'perror' to indicate that the format string ended-- early.---- @since 4.7.0.0errorShortFormat :: forall a. a errorShortFormat =String -> a forall a. String -> a perror String "formatting string ended prematurely"-- | Calls 'perror' to indicate that there is a missing-- argument in the argument list.---- @since 4.7.0.0errorMissingArgument :: forall a. a errorMissingArgument =String -> a forall a. String -> a perror String "argument list ended prematurely"-- | Calls 'perror' to indicate that there is a type-- error or similar in the given argument.---- @since 4.7.0.0errorBadArgument :: forall a. a errorBadArgument =String -> a forall a. String -> a perror String "bad argument"