[Haskell] Safe and generic printf with C-like format string

oleg at okmij.org oleg at okmij.org
Fri Jun 5 04:26:16 EDT 2009


The familiar printf is unsafe: nothing prevents us from passing to
printf more or fewer arguments than required by the format
specification, or passing the arguments of wrong types. The error is
discovered only at run-time. The implementation of printf in Haskell,
alas, retains this problem. There is also a desire to better integrate
printf with Show, so we can format the value of any showable type:
we'd like to have something like the ~a specification of Common Lisp.

Integrating printf with show, thus making it generic, is quite
easy. The implementation is still Haskell98. It has just been posted:

http://www.haskell.org/pipermail/haskell-cafe/2009-June/062410.html

Given its simplicity, one may wonder why it was not mentioned in the
Haskell98 report or included in standard libraries. The safety problem
still remains: we'd like to prevent the mismatch between
the arguments of printf and the format specification statically. That
too is easy to accomplish. Type-safe printf has been described by
Olivier Danvy back in 1998. It is part of SML/NJ. The only remaining
bit is to convert the formatting _string_ to the more representative
and more useful to the type-checker form. That too is easy, with
Template Haskell (as Ryan Ingram remarked).

The following code implements that suggestion. Aside from the use of
template Haskell, it is Haskell98. Beside the familiar format
specifications %s and %d, in implements the specification %a to
format any showable value. The code is available at
	http://okmij.org/ftp/typed-formatting/TotalPrintF.hs
	http://okmij.org/ftp/typed-formatting/TFTest.hs

The second file contains these examples:

module TFTest where

import TotalPrintF

t1 = printf $(spec "Hello, there!")
-- "Hello, there!"

t2 = printf $(spec "Hello, %s!") "there"
-- "Hello, there!"

t3 = printf $(spec "The value of %s is %d") "x" 3
-- "The value of x is 3"

-- Mismatch between the formatting string and the printf arguments
-- is a type error.

-- t31 = printf $(spec "The value of %s is %d") "x" True
--     Couldn't match expected type `Bool' against inferred type `Int'

{-
t32 = printf $(spec "The value of %s is %d") "x" 3 10
    Couldn't match expected type `t1 -> t'
           against inferred type `String'
    Probable cause: `printf' is applied to too many arguments
-}

t4 = let x = [9,16,25] 
	 i = 2 
     in printf $(spec "The element number %d of %a is %a") i x (x !! i)
-- "The element number 2 of [9,16,25] is 25"





More information about the Haskell mailing list