Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
An extensible and type-safe printf from parsing GHC TypeLits Symbol
literals, matching the semantics of printf
from Text.Printf in
base. The difference is that the variants here will always fail to
compile if given arguments of the wrong type (or too many or too little
arguments). Most of the variants also provide useful type feedback,
telling you the type of arguments it expects and how many when queried
with :t
or with typed holes. See documentation in Text.Printf for
details on how this formats items of various types, and the differences
with C printf(3)
.
There are three main calling conventions supported:
>>>
putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi>>>
putStrLn $ pprintf @"You have %.2f dollars, %s" (PP 3.62) (PP "Luigi")
You have 3.62 dollars, Luigi>>>
putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 :% "Luigi" :% RNil)
You have 3.62 dollars, Luigi
Now comparing their types:
>>>
:t printf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatFun '[ .... ] fun => fun>>>
:t pprintf @"You have %.2f dollars, %s" 3.62 "Luigi"
PP "f" -> PP "s" -> String>>>
:t rprintf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatArgs '["f", "s"] -> String
The type of
printf
doesn't tell you immediately what you you need. However, if you do try to use it, the type errors will guide you along the way, iteratively.>>>
printf @"You have %.2f dollars, %s"
-- ERROR: Call to printf missing argument fulfilling "%.2f" -- Either provide an argument or rewrite the format string to not expect -- one.>>>
printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi" 72
-- ERROR: An extra argument of type Integer was given to a call to printf -- Either remove the argument, or rewrite the format string to include the -- appropriate hole.- For
pprintf
, it shows you need two arguments: A
(which is a value that supports being formatted byPP
"f"f
) likePP 3.62
, and a
, likePP
"s"PP Luigi
. rprintf
tells you you need a two-item hlist (from Data.Vinyl.Core), where the first item implementsf
and the second item implementss
:3.62
will do.:%
Luigi :%RNil
The following table summarizes the features and drawbacks of each method:
Method | True Polyarity | Naked Arguments | Type feedback |
---|---|---|---|
printf | Yes | Yes | Partial (via errors) |
pprintf | Yes | No (requires PP ) | Yes |
rprintf | No (HList-based) | Yes | Yes |
Ideally we would have a solution that has all three. However, as of now, we have a "pick two" sort of situation. Suggestions are definitely welcome, however, if you find something that satisfies all three benefits while still allowing for polymorphism!
You can extend functionality with formatting for your own types by
providing instances of FormatType
.
Also in this module is pfmt
, which allows you to format individual
items according to a single format specifier.
Synopsis
- class FormatType (t :: SChar) a where
- formatArg :: p t -> a -> FieldFormat -> ShowS
- type SChar = Symbol
- printf :: forall str fun. Printf str fun => fun
- printf_ :: Printf str fun => p str -> fun
- data PHelp
- pHelp :: PHelp -> String
- class FormatFun (ffs :: [Either Symbol FieldFormat]) fun
- pprintf :: forall str ps. (RPrintf str ps, RecordCurry ps) => CurriedF PP ps String
- pprintf_ :: forall str ps p. (RPrintf str ps, RecordCurry ps) => p str -> CurriedF PP ps String
- data PP (c :: SChar) = forall a.FormatType c a => PP a
- rprintf :: forall str ps. RPrintf str ps => FormatArgs ps -> String
- rprintf_ :: RPrintf str ps => p str -> FormatArgs ps -> String
- data Rec (a :: u -> Type) (b :: [u]) where
- RNil :: forall u (a :: u -> Type). Rec a ('[] :: [u])
- pattern (:%) :: () => FormatType c a => a -> FormatArgs cs -> FormatArgs (c ': cs)
- type FormatArgs = Rec PP
- pfmt :: forall c a. FormatType c a => PFmt c -> a -> String
- data PFmt c
- mkPFmt :: forall str lst ff f w q m c. (Listify str lst, ff ~ ParseFmt_ lst, Reflect ff, ff ~ 'FF f w q m c) => PFmt c
- 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
Formattable things
class FormatType (t :: SChar) a where Source #
Typeclass associating format types (d
, f
, etc.) with the types
that can be formatted by them.
You can extend the printf methods here for your own types by writing your instances here.
Nothing
formatArg :: p t -> a -> FieldFormat -> ShowS Source #
Instances
Printf
Unguarded polyarity
printf :: forall str fun. Printf str fun => fun Source #
Type-safe printf with true naked polyarity. Call it like
.printf
@"you have %.02f dollars, %s"
>>>
putStrLn $ printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
While the type of
isn't going to be very
helpful, the error messages should help guide you along the way:printf
@"my fmt string"
>>>
printf @"You have %.2f dollars, %s"
-- ERROR: Call to printf missing argument fulfilling "%.2f" -- Either provide an argument or rewrite the format string to not expect -- one.
>>>
printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi" 72
-- ERROR: An extra argument of type Integer was given to a call to printf -- Either remove the argument, or rewrite the format string to include the -- appropriate hole.
If you're having problems getting the error messages to give helpful
feedback, try using pHelp
:
>>>
pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
pHelp
can give the type system the nudge it needs to provide good
errors.
See pprintf
for a version of this with nicer types and type errors,
but requires wrapping arguments, and rprintf
for a version of this
with "fake" polyarity, taking a list as input instead. Also see
top-level module documentation GHC.TypeLits.Printf for a more
comprehensive summary.
Note that this also supports the "interpret as an IO action to print out
results" functionality that Text.Printf supports. This also supports
returning strict Text
and lazy Text
as
well.
printf_ :: Printf str fun => p str -> fun Source #
A version of printf
taking an explicit
proxy, which allows usage without TypeApplications
>>>
putStrLn $ printf_ (Proxy :: Proxy "You have %.2f dollars, %s") 3.62 "Luigi"
You have 3.62 dollars, Luigi
A useful token for helping the type system give useful errors for
printf
:
>>>
printf @"You have ".2f" dollars, %s" 3.26 :: PHelp
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
Usually things should work out on their own without needing this ... but sometimes the type system could need a nudge.
See also pHelp
pHelp :: PHelp -> String Source #
A useful helper function for helping the type system give useful
errors for printf
:
>>>
pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
Usually things would work out on their own without needing this ... but sometimes the type system could need a nudge.
class FormatFun (ffs :: [Either Symbol FieldFormat]) fun Source #
The typeclass supporting polyarity used by
printf
. It works in mostly the same way as
PrintfType
from Text.Printf, and similar the same as
FormatF
.
Ideally, you will never have to run into this typeclass or have to deal
with it. It will come up if you ask for the type of
printf
, or sometimes if you give the wrong number
or type of arguments to it.
>>>
:t printf @"You have %.2f dollars, %s"
FormatFun '[ Right ..., 'Left " dollars ", 'Right ...] fun => fun
Every item in the first argument of FormatFun
is a chunk of the
formatting string, split between format holes (Right
) and string
chunks (Left
). You can successively "eliminate" them by providing
more arguments that implement each hole:
>>>
:t printf @"You have %.2f dollars, %s" 3.62
FormatFun '[ Right ...] fun => fun
Until you you finally fill all the holes:
>>>
:t printf @"You have %.2f dollars, %s" 3.62 "Luigi"
FormatFun '[] t => t
at which point you may use it as a String
or
, in the same
way that Text.Printf works. We also support using strict IO
()Text
lazy Text
as well.
So, while it's possible to reason with this using the types, it's
usually more difficult than with pprintf
and rprintf
.
This is why, instead of reasoning with this using its types, it's easier to reason with it using the errors instead:
>>>
printf @"You have %.2f dollars, %s"
-- ERROR: Call to printf missing argument fulfilling "%.2f" -- Either provide an argument or rewrite the format string to not expect -- one.
>>>
printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi"
You have 3.62 dollars, Luigi
>>>
printf @"You have %.2f dollars, %s" 3.62 "Luigi" 72
-- ERROR: An extra argument of type Integer was given to a call to printf -- Either remove the argument, or rewrite the format string to include the -- appropriate hole.
If you're having problems getting the error messages to give helpful
feedback, try using pHelp
:
>>>
pHelp $ printf @"You have %.2f dollars, %s" 3.62
-- ERROR: Call to printf missing argument fulfilling "%s" -- Either provide an argument or rewrite the format string to not expect -- one.
pHelp
can give the type system the nudge it needs to provide good
errors.
Instances
(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 # | |
Defined in GHC.TypeLits.Printf.Internal | |
a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) Text Source # | |
a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) Text Source # | |
a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) PHelp Source # | |
a ~ Char => FormatFun ('[] :: [Either Symbol FieldFormat]) [a] Source # | |
Defined in GHC.TypeLits.Printf.Internal | |
a ~ () => FormatFun ('[] :: [Either Symbol FieldFormat]) (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 # | |
Defined in GHC.TypeLits.Printf.Internal | |
(KnownSymbol str, FormatFun ffs fun) => FormatFun (('Left str :: Either Symbol FieldFormat) ': ffs) fun Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) PHelp Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) Text Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) Text Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) () Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) String Source # | |
(TypeError (MissingError ff) :: Constraint) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) (IO a) Source # | |
(Reflect ff, ff ~ 'FF f w p m c, FormatType c a, FormatFun ffs fun) => FormatFun (('Right ff :: Either Symbol FieldFormat) ': ffs) (a -> fun) Source # | |
Guarded polyarity
pprintf :: forall str ps. (RPrintf str ps, RecordCurry ps) => CurriedF PP ps String Source #
Type-safe printf with true guarded polyarity. Call it like
.pprintf
@"you have %.02f dollars, %s"
A call to printf on a valid string will always give a well-defined type for a function in return:
>>>
:t pprintf @"You have %.2f dollars, %s"
PP "f" -> PP "s" -> String
You can always query the type, and get a well-defined type back, which you can utilize using typed holes or other type-guided development techniques.
To give pprintf
its arguments, however, they must be wrapped in PP
:
>>>
putStrLn $ pprintf @"You have %.2f dollars, %s" (PP 3.62) (PP "Luigi")
You have 3.62 dollars, Luigi
See printf
for a polyariadic method that doesn't require PP
on its
inputs, but with a less helpful type signature, and rprintf
for
a fake-polyariadic method that doesn't require PP
, but requires
arguments in a single list instead. Also see top-level module
documentation GHC.TypeLits.Printf for a more comprehensive summary.
pprintf_ :: forall str ps p. (RPrintf str ps, RecordCurry ps) => p str -> CurriedF PP ps String Source #
A version of pprintf
taking an explicit proxy, which allows usage
without TypeApplications
>>>
:t pprintf_ (Proxy :: Proxy "You have %.2f dollars, %s")
PP "f" -> PP "s" -> String
Required wrapper around inputs to pprintf
(guarded polyarity). See documentation for
pprintf
for examples of usage.
You can "wrap" any value in PP
as long as it can be formatted as the
format type indicated.
For example, to make a
, you can use PP
"f"
or PP
3.5
, but not PP
94.2
or PP
(3 :: Int)
. To make a value of
type PP
"hello"
, you must wrap a value that can be formatted via PP
cc
.
forall a.FormatType c a => PP a |
List-based polyarity
rprintf :: forall str ps. RPrintf str ps => FormatArgs ps -> String Source #
Type-safe printf with faked polyarity. Pass in a "list" of arguments
(using :%
and RNil
), instead of as multiple arguments. Call it like
.rprintf
@"you have %.02f dollars, %s"
>>>
:t rprintf @"You have %.2f dollars, %s"
FormatArgs '["f", "s"] -> String
This means that it is expecting something that can be printed with f
and something that can be printed with s
. We can provide a Double
and a String
:
>>>
putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 ':%' "Luigi" :% 'RNil')
You have 3.62 dollars, Luigi
See pprintf
for a version with true polyarity and good clear types,
but requires wrapping its arguments, and printf
for a version with
true polyarity but less clear types. Also see top-level module
documentation GHC.TypeLits.Printf for a more comprehensive summary.
rprintf_ :: RPrintf str ps => p str -> FormatArgs ps -> String Source #
A version of rprintf
taking an explicit
proxy, which allows usage without TypeApplications
>>>
:t rprintf_ (Proxy :: Proxy "You have %.2f dollars, %s")
FormatArgs '["f", "s"] -> String
data Rec (a :: u -> Type) (b :: [u]) where #
A record is parameterized by a universe u
, an interpretation f
and a
list of rows rs
. The labels or indices of the record are given by
inhabitants of the kind u
; the type of values at any label r :: u
is
given by its interpretation f r :: *
.
pattern (:%) :: () => FormatType c a => a -> FormatArgs cs -> FormatArgs (c ': cs) infixr 7 | Pattern and constructor allowing you to construct a To construct a 3.62 (This should evoke the idea of of |
Instances
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss # | |
(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss # | |
RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f # | |
(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f # | |
TestCoercion f => TestCoercion (Rec f :: [u] -> Type) | |
Defined in Data.Vinyl.Core | |
TestEquality f => TestEquality (Rec f :: [u] -> Type) | |
Defined in Data.Vinyl.Core | |
Eq (Rec f ('[] :: [u])) | |
(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) | |
Ord (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core | |
(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering # (<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # | |
(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs) | Records may be shown insofar as their points may be shown.
|
Generic (Rec f ('[] :: [u])) | |
Generic (Rec f rs) => Generic (Rec f (r ': rs)) | |
Semigroup (Rec f ('[] :: [u])) | |
(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) | |
Monoid (Rec f ('[] :: [u])) | |
(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) | |
Storable (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core | |
(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core sizeOf :: Rec f (r ': rs) -> Int # alignment :: Rec f (r ': rs) -> Int # peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) # pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) # pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () # | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
Defined in Data.Vinyl.Lens | |
type Rep (Rec f (r ': rs)) | |
Defined in Data.Vinyl.Core type Rep (Rec f (r ': rs)) = C1 ('MetaCons ":&" ('InfixI 'RightAssociative 7) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f r)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rep (Rec f rs))) | |
type Rep (Rec f ('[] :: [u])) | |
Defined in Data.Vinyl.Core |
type FormatArgs = Rec PP Source #
A heterogeneous list (from Data.Vinyl.Core) used for calling with
rprintf
. Instead of supplying the inputs as
different arguments, we can gather all the inputs into a single list to
give to rprintf
.
>>>
:t rprintf @"You have %.2f dollars, %s"
FormatArgs '["f", "s"] -> String
To construct a
, you need to give a value
formattable by FormatArgs
'["f", "s"]f
and a value formattable by s
, given like a linked
list, with :%
for cons and RNil
for nil.
>>>
putStrLn $ rprintf @"You have %.2f dollars, %s" (3.62 :% "Luigi" :% RNil)
You have 3.62 dollars, Luigi
(This should evoke the idea of of 3.62 : Luigi : []
, even though the
latter is not possible in Haskell)
Single item
pfmt :: forall c a. FormatType c a => PFmt c -> a -> String Source #
Parse and run a single format hole on a single vale. Can be useful
for formatting individual items or for testing your own custom instances of
FormatType
.
Usually meant to be used with OverloadedLabels:
>>>
pfmt #f 3.62
"3.62"
However, current versions of GHC disallow labels that aren't valid
identifier names, disallowing things like
. 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 pfmt
#.2f 3.62mkPFmt
:
>>>
pfmt (mkPFmt @".2f") 3.6234124
"3.62"
Ideally we'd want to be able to write
>>>
pfmt #.2f 3.6234124
"3.62"
(which should be possible in GHC 8.10+)
Note that the format string does not include the leading %
.
Utility type powering pfmt
. See dcumentation for pfmt
for more
information on usage.
Using OverloadedLabels, you never need to construct this directly
can just write #f
and a
will be generated. You can also
create this using PFmt
"f"mkPFmt
or mkPFmt_
, in the situations where
OverloadedLabels doesn't work or is not wanted.
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"