[Haskell-cafe] Re: [Haskell] The initial view on typed sprintf and sscanf

Matthew Brecknell haskell at brecknell.org
Mon Sep 1 03:40:49 EDT 2008


oleg [1]:
> We demonstrate typed sprintf and typed sscanf sharing the same
> formatting specification.

[1]http://www.haskell.org/pipermail/haskell/2008-August/020605.html

Reading Oleg's post, I noticed that it is quite straightforward to
generalise printing to arbitrary output types.

> class Monoid p => Printf p where
>   printChar :: Char -> p
>   --etc
> 
> intp :: Printf p => F a b -> (p -> a) -> b
> intp FChr k = \c -> k (printChar c)
> intp (a :^ b) k = intp a (\sa -> intp b (\sb -> k (mappend sa sb)))
> --etc
> 
> printf :: Printf p => F p b -> b
> printf fmt = intp fmt id

The Printf instances for String, ShowS, ByteStrings, and IO () are all
trivial.

Printing directly to a file (without building an intermediate string) is
slightly more interesting:

> instance Monad m => Monoid (ReaderT r m ()) where
>   mempty = return ()
>   mappend = (>>)
> 
> instance Printf (ReaderT Handle IO ()) where
>   printChar c = ask >>= \h -> liftIO (hPutChar h c)
>   --etc
> 
> (<<) :: Handle -> ReaderT Handle IO () -> IO ()
> (<<) = flip runReaderT
>
> test_fprintf h = h << printf (lit "Hello " ^ lit "World" ^ chr) '!'

Unfortunately, I don't seem to be able to make the expected fprintf
function, because printf's format-dependent parameter list makes it
impossible to find a place to pass the handle. Hence the C++-like (<<)
ugliness.



More information about the Haskell-Cafe mailing list