
Hi all, I am writing, for my own amusement, a more general version of the trick to implement variadic functions in Haskell outlined at http://okmij.org/ftp/Haskell/vararg-fn.lhs. (If someone else has done this already, please point me to it!) Code is attached at the end of the message. My question concerns the use of `typeCast', which is defined as follows: class TypeCast x y | x -> y, y -> x where typeCast :: x -> y instance TypeCast x x where typeCast = id This is taken from the paper "Strongly typed heterogeneous collections" by Oleg Kiselyov, Ralf Lammel, and Keean Schupke. As observed there, the TypeCast instance declaration must occur in a separate module; otherwise the compiler is too eager about type simplification. (I also get the same errors if VarArg is interpreted by GHCi, even if TypeCast is in a separate module.) I think I understand the reason for this, but I find it a little surprising; it wasn't clear to me from the documentation that fundeps introduce a new dependence on module boundaries. Anyway, my main question about typeCast is this: why is it needed here at all? If I omit it entirely, the code compiles fine, but then using it gives error messages like the following: Prelude VarArg> build 'h' 'i' :: String <interactive>:1:0: No instances for (VarFold [a] [a] [Char], VarAccum Char [a]) arising from use of `build' at <interactive>:1:0-4 ... I don't understand why the type-checker is unable to infer that the type variable `a' should be specialized to `Char' here, since the only available instance of VarFold whose third type is [Char] has the first type also being [Char]. I've given the compiler all the type hints I can think of. Can someone explain this to me? I should say that if I add a functional dependency "l -> a" to the class VarAccum, then this particular example works. However, I have other examples in mind for which l doesn't functionally determine a, so I don't want to do that. And I don't see why it's necessary. Here's the code: class VarAccum a l where accum :: a -> l -> l class VarFold b l r where varFold :: (l -> b) -> l -> r instance (TypeCast b c) => VarFold b l c where varFold f xs = typeCast (f xs) instance (VarFold b l r, VarAccum a l) => VarFold b l (a -> r) where varFold f xs x = varFold f (accum x xs) -- This is the type of variadic functions from lots of As to a B. type a :--> b = forall r. (VarFold b [a] r) => r infixr 0 :--> instance VarAccum a [a] where accum x xs = (x:xs) varArg :: forall a b. ([a] -> b) -> (a :--> b) varArg f = varFold (f . reverse) ([] :: [a]) build :: forall a. a :--> [a] build = varArg (id :: [a] -> [a]) Thanks! Mike