
Hello Ryan, Monday, September 1, 2008, 12:16:46 PM, you wrote: of course this may be done with code generation tools (such as TH). point of this research is to do this using type abilities of Haskell Don, i think this should be impossible with IsString since the point is that Haskell compiler should know types at compile time. IsString can't convert "%d" into (X int) while converting "%s" into (X String)
On Mon, Sep 1, 2008 at 1:00 AM, Don Stewart
wrote: I also wonder if we could give a String syntax to the formatting language, using -XOverloadedStrings and the IsString class.
Probably easier with Template Haskell:
ghci -fth Sprintf.hs *Sprintf>> :t $(sprintf "Hello %s, showing %S and %S") $(sprintf "Hello %s, showing %S and %S") :: (Show a1, Show a) => [Char] -> a -> a1 -> [Char] *Sprintf>> $(sprintf "Hello %s, showing %S and %S") "Don" 1 (5,6) "Hello Don, showing 1 and (5,6)"
Code follows, which could be ported to use the printf/scanf language Oleg defined.
-- ryan
{-# LANGUAGE TemplateHaskell #-} module Sprintf where import Language.Haskell.TH
data SprintfState = SprintfState String (ExpQ -> ExpQ)
flush :: SprintfState -> (ExpQ -> ExpQ) flush (SprintfState "" k) = k flush (SprintfState s k) = (\e -> k [| $(litE $ StringL $ reverse s) ++ $e |])
finish :: SprintfState -> ExpQ finish (SprintfState s k) = k (litE $ StringL $ reverse s)
addChar :: Char ->> SprintfState -> SprintfState
addChar c (SprintfState s e) = SprintfState (c:s) e
addCode :: ExpQ ->> SprintfState -> SprintfState
addCode k s = SprintfState "" (\e -> flush s $ [| $k ++ $e |])
sprintf' :: SprintfState -> String -> ExpQ sprintf' k ('%':'S':cs) = [| \x -> $(sprintf' (addCode [| show x |] k) cs) |] sprintf' k ('%':'s':cs) = [| \s -> $(sprintf' (addCode [| s |] k) cs) |] sprintf' k ('%':'%':cs) = sprintf' (addChar '%' k) cs sprintf' k (c:cs) = sprintf' (addChar c k) cs sprintf' k [] = finish k
sprintf :: String ->> ExpQ
sprintf = sprintf' (SprintfState "" id) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com