[Haskell-cafe] untyped printf
Henning Thielemann
lemming at henning-thielemann.de
Fri Dec 4 18:06:15 UTC 2020
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
More information about the Haskell-Cafe
mailing list