
I am writing an interpreter for a very simple untyped language and I want to provide a built-in function to format a list of values in a printf like fashion. There is the beautiful Text.Printf module with its multi-variadic printf function, and I would like to use that to do all the heavy lifting. I can easily implement an instance PrintfArg Value for my Value type, but what I need in addition to that is an "untyped" version of printf i.e. something like format :: String -> [Value] -> String with the property that format fmt [] = printf fmt format fmt [x] = printf fmt x format fmt [x,y] = printf fmt x y ... I am pretty sure this is possible using a bit of class hackery and perhaps GADTs or continuation passing thrown in, but I can't seem to get it working. Any hint that helps to untangle the knots in my brain would be appreciated! Cheers Ben

On Fri, 4 Dec 2020, Ben Franksen wrote:
I am writing an interpreter for a very simple untyped language and I want to provide a built-in function to format a list of values in a printf like fashion. There is the beautiful Text.Printf module with its multi-variadic printf function, and I would like to use that to do all the heavy lifting.
I can easily implement an
instance PrintfArg Value
for my Value type, but what I need in addition to that is an "untyped" version of printf i.e. something like
format :: String -> [Value] -> String
with the property that
format fmt [] = printf fmt format fmt [x] = printf fmt x format fmt [x,y] = printf fmt x y ...
{-# LANGUAGE Rank2Types #-} import Text.Printf (PrintfType, printf) type Value = Int formatWith :: (forall t. (PrintfType t) => t) -> [Value] -> String formatWith pf [] = pf formatWith pf (x:xs) = formatWith (pf x) xs format :: String -> [Value] -> String format fmt = formatWith (printf fmt) *Main> format "(%d,%d)" [1,2] "(1,2)" *Main> format "(%d,%d)" [1,2,3] "(1,2)*** Exception: printf: formatting string ended prematurely *Main> format "(%d,%d)" [1] "(1,*** Exception: printf: argument list ended prematurely

Wow, that simple. Thanks Henning, my untangled brain feels a lot better :-) Cheers Ben Am 04.12.20 um 19:06 schrieb Henning Thielemann:
On Fri, 4 Dec 2020, Ben Franksen wrote:
I am writing an interpreter for a very simple untyped language and I want to provide a built-in function to format a list of values in a printf like fashion. There is the beautiful Text.Printf module with its multi-variadic printf function, and I would like to use that to do all the heavy lifting.
I can easily implement an
instance PrintfArg Value
for my Value type, but what I need in addition to that is an "untyped" version of printf i.e. something like
format :: String -> [Value] -> String
with the property that
format fmt [] = printf fmt format fmt [x] = printf fmt x format fmt [x,y] = printf fmt x y ...
{-# LANGUAGE Rank2Types #-} import Text.Printf (PrintfType, printf)
type Value = Int
formatWith :: (forall t. (PrintfType t) => t) -> [Value] -> String formatWith pf [] = pf formatWith pf (x:xs) = formatWith (pf x) xs
format :: String -> [Value] -> String format fmt = formatWith (printf fmt)
*Main> format "(%d,%d)" [1,2] "(1,2)"
*Main> format "(%d,%d)" [1,2,3] "(1,2)*** Exception: printf: formatting string ended prematurely
*Main> format "(%d,%d)" [1] "(1,*** Exception: printf: argument list ended prematurely _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Fri, 4 Dec 2020, Ben Franksen wrote:
Wow, that simple. Thanks Henning, my untangled brain feels a lot better :-)
I tangled my brain because I expected that it must be possible in Haskell 98 ... ... and actually it is: import Text.Printf (PrintfType, printf) type Value = Int printfv :: (PrintfType printf) => String -> [Value] -> printf printfv fmt [] = printf fmt printfv fmt (x:xs) = printfv fmt xs x format :: String -> [Value] -> String format fmt = printfv fmt . reverse
participants (2)
-
Ben Franksen
-
Henning Thielemann