Search code examples
haskellprintfpolyvariadic

How to create a polyvariadic function which itself uses another polyvariadic function (e.g. printf)?


I'm trying to write the below function so that I can use it with a variable number of arguments to Text.Printf.printf. I tried using typeclasses but I couldn't find any example which wasn't processing the format string character by character and argument by argument. I was hoping it would be possible to capture all the arguments and pass it to printf at once.

-- panic :: PrintfType r -> Int -> String -> r

panic lvl fmt =
    let fail :: String -> String -> a
        fail s s' = error $ printf "%s: %s" s s'
    in flip fail (show lvl) . printf fmt

I want to use the function like this:

panic 0 "Err"                   -- Exception: "Err: 0"
panic 1 "Err %s %d" "fatal" 42  -- Exception: "Err fatal 42: 1"

How should I proceed with its implementation?


Solution

  • It can be done, but as noted in the comments, everything about Text.Printf is a hack. The hack is done with typeclass resolution. printf has a typeclass (whose implementation is not exposed) called PrintfType which is implemented for ground types (IO () and String) but also for function types a -> r, which allows us to pretend Haskell has variadic parameters.

    Like I said, the typeclass implementation isn't exposed. But fortunately, we can write our own. First, let's get the header out of the way.

    {-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances, TypeFamilies #-}
    

    As with advanced typeclass features, we need some compiler extensions. Now here's the class we're going to work with.

    class PanicType t where
        type Prev t
        spr :: (String -> Void) -> Prev t -> t
    

    Our function spr takes a postprocessing function String -> Void which will take our "compiled" string and bottom out by calling error. Then we take the "previous" step of the computation and produce a t, which may take some arguments and will eventually produce a Void as well. (We don't encode the "eventually a Void" constraint in our typeclass, but the instances we write will force us to do it anyway).

    As an interlude, this is one concession we have to make. Ideally, your panic function eventually returns forall b. b. I don't know of a good way to make a variadic function do that, since there will be overlapping typeclasses galore (every typeclass instance would necessarily overlap with our "catch-all" one). It might be doable with OverlappingInstances, but every time I poke around in that side of Haskell, it ends in tears.

    Now we'll need two instances of this typeclass. I'm using all of the nice "flexible" GHC extensions, so we won't have to do quite as much hackery as printf does. One instance will be for Void, our ground term that we hit at the end of passing arguments. The other will be for a -> r and admits another argument.

    instance PanicType Void where
        type Prev Void = String
        spr post k = post k
    

    When we hit our ground term, we can assume the "thing we've built up" continuation argument is a String. So we just call our postprocessor (which will be error-with-benefits, in practice).

    instance (PrintfArg a, PanicType r, PrintfType (Prev r)) => PanicType (a -> r) where
        type Prev (a -> r) = (a -> Prev r)
        spr post k a = spr post (k a)
    

    Now the case where we accept another argument. The "previous" continuation for a -> r is merely defined recursively as a function which takes an a and produces a Prev r. Then our spr delegates to spr on PanicType r.

    Note that the hard part is coming up with the types. Once we decide on the type of spr and Prev, the function implementations are largely technical and just write themselves.

    Now for panic. We need to call spr for our r result type, with a postprocessing argument that will invoke error and with a continuation argument that starts a printf. Like this.

    panic :: (PanicType r, PrintfType (Prev r)) => Int -> String -> r
    panic lvl fmt = spr (\s -> error (printf "%s: %s" s (show lvl))) (printf fmt)
    

    Like I said, we do eventually get a Void, not a forall b. b, so you have to absurd the result in practice.

    main :: IO ()
    main = absurd (panic 0 "Err %s %d" "fatal" (42 :: Int))
    

    And welcome to the dark side of Haskell! Check your jacket at the door, cookies are available on the table.

    Try it online!