preprocessing printf/regex strings (like ocaml)
Sebastien Carlier
sebc@wise-language.org
Tue, 14 May 2002 11:59:28 +0200
--Apple-Mail-2-113496249
Content-Transfer-Encoding: 7bit
Content-Type: text/plain;
charset=US-ASCII;
format=flowed
On Tuesday, May 14, 2002, at 06:37 AM, anatoli wrote:
> Brian Huffman <bhuffman@galois.com> wrote:
>> Here is a printf-style function that I hacked up this morning; it uses
>> type
>> classes but it doesn't need functional dependencies:
> [snip]
>
> It's very nice and even extendable, though `class Printf String'
> is unfortunately not Haskell 98.
I agree that it is a very nice use of type classes. But all type
checking
is done at runtime, because the code which is generated depends not
on the string itself, but on the types of the arguments which are applied
to (printf <<format string>>).
For example,
putStrLn $ printf "%s" (1 :: Integer)
gives no error at compilation, but fails at runtime with:
Program error: printf: extra integer argument
> But the bigger question is, how to support Posix-style positional
> arguments? They are essential for i18n.
I hacked Brian's code to add this feature, see the attachment.
--Apple-Mail-2-113496249
Content-Disposition: attachment;
filename=Printf.hs
Content-Transfer-Encoding: 7bit
Content-Type: application/octet-stream;
x-unix-mode=0644;
name="Printf.hs"
module Printf where
main =
do putStrLn $ printf "%i * %c = %d %s." (2::Integer) 'c' (6.0e8::Double) "meters/sec"
putStrLn $ printf "foo is %2$s, bar is %1$s." "bar" "foo"
a # b = b a
class Printf a where
printf :: String -> a
printf pat = printf' 0 [] (const id) pat
printf' :: Int -> [ShowS] -> ([ShowS] -> ShowS) -> String -> a
instance Printf String where
printf' n xs k pat = (k xs . showString pat) ""
instance (Format a, Printf b) => Printf (a -> b) where
printf' n xs k pat = \ x ->
break ('%'==) pat # \ (text, ('%':pat')) ->
format pat' n x # \ (k', x', rest) ->
printf' (n + 1) (xs ++ [x']) (\ xs -> k xs . showString text . k' xs) rest
class Format a where
format :: String -> Int -> a -> ([ShowS] -> ShowS, ShowS, String)
format pat@(c:_) n x | isDigit c =
break ('$'==) pat # \ (pos, ('$':pat')) ->
format pat' (read pos - 1 :: Int) x
format pat n x =
format' pat x # \ (f, rest) ->
(\ xs -> xs!!n, f, rest)
format' :: String -> a -> (ShowS, String)
instance Format String where
format' ('s':rest) x = (showString x, rest)
instance Format Char where
format' ('c':rest) x = (showString [x], rest)
instance Format Integer where
format' ('i':rest) x = (shows x, rest)
instance Format Double where
format' ('d':rest) x = (shows x, rest)
--Apple-Mail-2-113496249
Content-Transfer-Encoding: quoted-printable
Content-Type: text/plain;
charset=ISO-8859-1;
format=flowed
> For instance,
>
>> printf "%1$s %2$s" "foo" "bar" -- =3D=3D> "foo bar"
>> printf "%2$s %1$s" "foo" "bar" -- =3D=3D> "bar foo"
>
> Naturally, such format strings cannot be pre-processed by the
> compiler since they are typically loaded from some message
> database at run time.
Then you give up static type checking for format strings...
Why not let the compiler pre-process this database, and generate
some type-safe dynamically loadable object ?
Or, you could embed a very restricted version of the compiler in
the program, to pre-process and type-check the format strings at runtime
(Yes, you would need to keep some type information in the executable
program).
--
S=E9bastien
--Apple-Mail-2-113496249--