I am trying to implement keyword arguments in Haskell, similar to the ones found in Ocaml. My goal is to have arguments that can be passed in any order, and can be partially applied in a function call (yielding a new function that takes the remaining keyword arguments).
I've tried to implement this using DataKinds and a type-class that represents "a value that can be converted into a function a -> b
." The idea is that a function taking two keyword arguments, foo
and bar
, can be converted either to a function that looks like foo -> bar -> x
or to a function that looks like bar -> foo -> x
. This should be unambiguous so long as foo
and bar
have different types (and x
isn't itself a function that takes foo
or bar
), which is what I've tried to achieve with the Kwarg
GADT.
The functional dependency in the Fun
class was meant to make the relationship between f
, a
, and b
more explicit, but I'm not sure whether this actually helped. I get a compiler error with and without it.
I have enabled the following language extensions:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
Contents of Quoter.hs
:
module Quoter where
import GHC.TypeLits (Symbol)
data Kwarg :: Symbol -> * -> * where
Value :: a -> Kwarg b a
class Fun f a b | f a -> b where
runFun :: f -> a -> b
instance (Fun f' a' b) => Fun (a -> f') a' (a -> b) where
runFun f a' = \a -> runFun (f a) a'
instance Fun (Kwarg name t -> b) (Kwarg name t) b where
runFun = id
Contents of Main.hs
:
module Main where
import Quoter
test :: (Num a) => Kwarg "test" a -> Kwarg "some" a -> a
test (Value i) (Value j) = i + j
main = putStrLn $ show $
runFun test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int)
This is the error that I get when building with ghc:
Main.hs:18:3: error:
• Couldn't match type ‘Kwarg "some" Int -> b’ with ‘Int’
arising from a functional dependency between:
constraint ‘Fun (Kwarg "some" Int -> Int) (Kwarg "some" Int) Int’
arising from a use of ‘runFun’
instance ‘Fun (a -> f') a' (a -> b1)’ at <no location info>
• In the second argument of ‘($)’, namely
‘runFun
test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int)’
In the second argument of ‘($)’, namely
‘show
$ runFun
test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int)’
In the expression:
putStrLn
$ show
$ runFun
test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int)
Do you know what I need to change in order to get this to compile? Is this general approach sensible, and what do I need to understand better in order to get this to work?
Thanks!
Output of ghc --version
:
The Glorious Glasgow Haskell Compilation System, version 8.0.2
The problem is that your instances are overlapping:
instance (Fun f' a' b) => Fun (a -> f') a' (a -> b) where
instance Fun (Kwarg name t -> b) (Kwarg name t) b
-- this is actually a special case of the above, with a ~ a' ~ KWarg name t
It becomes clearer if we replace the functional dependency (which is IMO usually a bit hard to reason about) with an equivalent associated type family:
{-# LANGUAGE TypeFamilies #-}
class Fun f a where
type FRes f a :: *
runFun :: f -> a -> FRes f a
instance Fun f' a' => Fun (a -> f') a' where
type FRes (a -> f') a' = a -> FRes f' a'
runFun f a' = \a -> runFun (f a) a'
instance Fun (Kwarg name t -> b) (Kwarg name t) where
type FRes (Kwarg name t -> b) (Kwarg name t) = b
runFun = id
In this case, the compiler message is pretty clear:
Conflicting family instance declarations:
FRes (a -> f') a' = a -> FRes f' a'
-- Defined at /tmp/wtmpf-file10498.hs:20:8
FRes (Kwarg name t -> b) (Kwarg name t) = b
-- Defined at /tmp/wtmpf-file10498.hs:24:8
|
20 | type FRes (a -> f') a' = a -> FRes f' a'
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Overlapping instances are a big problem, in particular when nontrivial type-level functions need to be resolved. However, it's not a problem that hasn't been encountered often before. A solution is to switch from the instance-clause-based type-level functions (i.e. FunDeps or associated type-families) to closed type families:
type family FRes f a where
FRes (Kwarg name t -> b) (Kwarg name t) = b
FRes (a -> f') a' = a -> FRes f' a'
To actually implement runFun
, you still need a class with overlapping instances, however these can now be hacked to worked with GHC pragmas:
class Fun f a where
runFun :: f -> a -> FRes f a
instance {-# OVERLAPPABLE #-} (Fun f' a', FRes (a -> f') a' ~ (a->FRes f' a'))
=> Fun (a -> f') a' where
runFun f a' = \a -> runFun (f a) a'
instance {-# OVERLAPS #-} Fun (Kwarg name t -> b) (Kwarg name t) where
runFun = id
As such, your test will now work.
Unfortunately it will not do what it's actually supposed to though: allow the argument order to be changed.
main = putStrLn $ show
( runFun test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int)
, runFun test (Value 5 :: Kwarg "test" Int) (Value 6 :: Kwarg "some" Int) )
gives
/tmp/wtmpf-file10498.hs:34:5: error:
• Couldn't match expected type ‘Kwarg "some" Int -> b0’
with actual type ‘FRes
(Kwarg "test" a0 -> Kwarg "some" a0 -> a0) (Kwarg "test" Int)’
The type variables ‘a0’, ‘b0’ are ambiguous
• The function ‘runFun’ is applied to three arguments,
but its type ‘(Kwarg "test" a0 -> Kwarg "some" a0 -> a0)
-> Kwarg "test" Int
-> FRes
(Kwarg "test" a0 -> Kwarg "some" a0 -> a0) (Kwarg "test" Int)’
has only two
In the expression:
runFun
test (Value 5 :: Kwarg "test" Int) (Value 6 :: Kwarg "some" Int)
In the first argument of ‘show’, namely
‘(runFun
test (Value 5 :: Kwarg "some" Int) (Value 6 :: Kwarg "test" Int),
runFun
test (Value 5 :: Kwarg "test" Int) (Value 6 :: Kwarg "some" Int))’
|
34 | , runFun test (Value 5 :: Kwarg "test" Int) (Value 6 :: Kwarg "some" Int) )
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
The essential problem is that type inference goes in the less favourable direction: from starting-values to end-results. This is the only avaible direction in most languages, but in Haskell it's almost always better to infer from the end result to the individual expressions, because only the outer result is always available for unification with the environment. In the end, that leads you to something like
type family FFun a b where
i.e. the type of function is determined from the result you want and the argument you can already supply. You would then not have overlapping instances based on whether the argument at hand happens to be the first one the function expects; rather you'd build up some sort of type-level map including all the keyed arguments and have the function accept one such map (or, equivalently, all the arguments in alphabetic order).