Variable-arity currying helper

Prompted by a need from a project and inspired by The Haskell Unfolder E26, I created a small demo of variable-arity currying helper that wraps any Haskell function whose arguments have Show instance, trace them, and return the result back as expected.

#!/usr/bin/env -S cabal run -v1
{- cabal:
build-depends: base
default-language: GHC2024
ghc-options: -Wall
-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}

import           Debug.Trace (trace)

-- | Variable-arity currying helper for any function wrapper @f@ that takes curries a @a@ and returns a @b@.
class MagicCurry f a b where
  curry' :: f -> a -> b

-- | Simple function wrapper for any Husk functions, whose `MagicCurry` instances traces all its arguments.
data Fn f where MkFn :: forall f. f -> Fn f

instance {-# OVERLAPPABLE #-} (Show a, Show b) => MagicCurry (Fn (a -> b)) a b where
  curry' (MkFn f) a = trace (show a) (f a)

instance (Show a, MagicCurry (Fn (b -> c)) b c) => MagicCurry (Fn (a -> b -> c)) a (b -> c) where
  curry' (MkFn f) a b = trace (show a) (curry' (MkFn (f a)) b)

{- DEMO -}

foo :: String -> Int -> Bool -> String
foo l i b = if b then l ++ ": " ++ show i else l ++ ": nah"

main = do
  let foo' = curry' (MkFn foo)
  putStrLn (foo' "Hello: " (42 :: Int) True)
  putStrLn (foo' "Hello: " (69 :: Int) False)
$ ./magic-curry.hs 
"Hello: "
42
True
Hello: : 42
"Hello: "
69
False
Hello: : nah
3 Likes

I see what this does and why it’s useful, but I don’t understand why you’re calling what it’s doing currying, since the input function is already curried.

Indeed, it is not the most accurate naming.

My best attempt of trying to categorize the general problem is:

In Haskell, how do you create an n-arity (hence currying) function whose arity depends on the input type?

In the example I gave above, the input type is any-arity function with all arguments having Show instances.

Not a great answer to any question, but I believe “variable-arity” is called “variadic”

I have shared this too often but here is it again since it fits the topic - this little thingy rewrites a function to a function that takes an n-ary product (curries it) and then sorts it such that it fits naming requirements and then it uses the new setField overloading to get named arguments (very cool, no)

The problem with these functions is always that the last one may overlap, so (b -> a) isn’t actually fully determined since a could be c -> d, so you either need to use OVERLAPPING pragmas or write a tiny eDSL that replaces functions in a way that is safe (not ergonomic). Another possibility would be to write a wrapper newtype NoFunction that you put around the last argument of a function to signal to the type checker that it should stop currying there.

https://bin.mangoiv.com/note?id=d204d07f-6292-4eb7-9aff-4cabc78394b9

Sooooo when overloaded record update is stabilized, we get named function arguments for free! You gotta love Haskell for these kinda things.

1 Like

Interesting share.

I have a quick question:

What’s the concern here? I admit when I looked the whole segment about overlapping instances, it is scary. But after reading the rules, I realized that, as long as I don’t have to enable “Incoherent” extension or the incoherent pragma for the instance, the rule seems clear enough and, hence, hopefully safe.

Is that hope wrong?

P.S. excerpt of the rules:

  • Find all instances I that match the target constraint; that is, the target constraint is a substitution instance of I* . These instance declarations are the candidates.
  • If no candidates remain, the search fails
  • Eliminate any candidate IX for which there is another candidate IY such that both of the following hold:
    • IY is strictly more specific than IX. That is, IY is a substitution instance of IX* but not vice versa.
    • IX is overlappable or IY* * is overlapping. (This “or” design, rather than an “and” design, allows a client to deliberately override an instance from a library, without requiring a change to the library.)
  • If all the remaining candidates are incoherent, the search succeeds, returning an arbitrary surviving candidate.
  • If more than one non-incoherent candidate remains, the search fails.
  • Otherwise there is exactly one non-incoherent candidate; call it the “prime candidate”.
  • Now find all instances, or in-scope given constraints, that unify with the target constraint, but do not match it. Such non-candidate instances might match when the target constraint is further instantiated. If all of them are incoherent top-level instances, the search succeeds, returning the prime candidate. Otherwise the search fails.

The concern is that it doesn’t work if the “tail” is ambiguous as shown in my example.

b -> a could either have a ~ SomeSpecialType with parameters or a ~ c -> d, so you will get an OVERLAPPING instances error.

In the codesnippet I shared, try to make exp’ return a Num a => which should be perfectly fine if you call fromIntegral on the result.

And it’s also fine in the sense that we know that _ -> _ doesn’t have a Num instance but the constraint solver cannot and could not possibly refute it, for the simple reason that the instance that we need could just not be in scope.

1 Like

as said in the in warning incoherence can rise even with Overlapping instances alone, if you did the trick in the warning but instead of values you used type families a crash may happen granted it isn’t easy but we generally aren’t C programmers.
Edit: actually i was wrong GHC won’t allow conflicting Type families instances so they must always agree

I wrote the multicurryable library in Hackage which, like your example, uses the NP products from sop-core for the “uncurried” arguments.

variable-arity currying helper that wraps any Haskell function whose arguments have Show instance, trace them, and return the result back as expected.

These kinds of decorators are very useful, and perhaps a bit underused I think. You can go further and write code that decorates entire records-of-functions.

2 Likes