[Haskell-cafe] Re: [Haskell] The initial view on typed sprintf and
sscanf
ChrisK
haskell at list.mightyreason.com
Tue Sep 2 06:13:56 EDT 2008
Matthew Brecknell wrote:
> 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.
How about this:
> fprintf :: Handle -> F (IO ()) b ->
> fprintf h fmt = write fmt id where
> write :: F a b -> (IO () -> a) -> b
> write (FLit str) k = k (hPutStr h str)
> write FInt k = \i -> k (hPutStr h (show i))
> write FChr k = \c -> k (hPutChar h c)
> write (FPP (PrinterParser pr _)) k = \x -> k (hPutStr h (pr x))
> write (a :^ b) k = write a (\sa -> write b (\sb -> k (sa >> sb)))
*PrintScan> fprintf stdout fmt5 15 1.3 '!'
abc15cde1.3!*PrintScan>
The first thing I did last night was change String to
type ShowS = String -> String :
> intps :: F a b -> (ShowS -> a) -> b
> intps (FLit str) k = k (str++)
> intps FInt k = \x -> k (shows x)
> intps FChr k = \x -> k (x:)
> intps (FPP (PrinterParser pr _)) k = \x -> k (pr x ++)
> intps (a :^ b) k = intps a (\sa -> intps b (\sb -> k (sa . sb)))
> sprintfs :: F ShowS b -> b
> sprintfs fmt = intps fmt id
Ideally PrinterParser would display using "ShowS" as well:
> data PrinterParser a
> = PrinterParser (a -> ShowS) (String -> Maybe (a, String))
Or one could use instance witnesses via GADTs to wrap up Show:
> data F a b where
> FSR :: (Show b,Read b) => F a (b -> a)
But I think changing PrinterParser would result in simpler code.
Cheers,
Chris
More information about the Haskell-Cafe
mailing list