preprocessing printf/regex strings (like ocaml)
Brian Huffman
bhuffman@galois.com
Mon, 13 May 2002 11:02:46 -0700
On Sunday 12 May 2002 03:50 am, Sebastien Carlier wrote:
> >>> the python string notation (str % tuple) would fit really well too...
> >>> putStrLn "hello %s, you got %d right" % ("oliver", 5)
> >>
> >> Might be nice.
> >
> > What would be the type of putStrLn then?
>
> The type of putStrLn would remain unchanged.
>
> The idea would be to let the compiler translate the string
> "hello %s, you got %d right"
> into the function
> (\ (p1, p2) -> "hello " ++ p1 ++ ", you got " ++ show p2 ++ " right")
> so that the type system can do its work. Then the % above is only an
> application.
> There is of course no need for the tuple; a curried function would
> probably be more convenient.
Here is a printf-style function that I hacked up this morning; it uses type
classes but it doesn't need functional dependencies:
module Printf where
main = putStrLn $ printf "%i * %c = %d %s."
(2::Integer) 'c' (6.0e8::Double) "meters/sec"
class Printf a where
printf :: String -> a
printf' :: ShowS -> String -> a
printf = printf' id
instance Printf String where
printf' pre pattern = pre pattern
instance (Format a, Printf b) => Printf (a -> b) where
printf' pre pattern x =
let (text, pat') = break ('%'==) pattern
(formatted, rest) = format x pat'
in printf' (pre . showString text . showString formatted) rest
--------------------------------------------
class Format a where
format :: a -> String -> (String, String)
instance Format Char where
format c pat = case pat of
'%':'c':rest -> ([c],rest)
_ -> error "printf: extra char argument"
instance Format String where
format s pat = case pat of
'%':'s':rest -> (s,rest)
_ -> error "printf: extra string argument"
instance Format Integer where
format i pat = case pat of
'%':'i':rest -> (show i,rest)
_ -> error "printf: extra integer argument"
instance Format Double where
format d pat = case pat of
'%':'d':rest -> (show d,rest)
_ -> error "printf: extra double argument"