Accepting and returning polyvariadic functions

Hi all, I'm trying to write a function (I'll call it `vtuple' for lack of a better name) that returns a function that itself returns multiple arguments in the form of a tuple. For example:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-}
f :: Int -> IO () f = undefined
g :: Int -> Int -> IO () g = undefined
h :: Int -> Int -> Int -> IO () h = undefined
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ()))) I've tried to type vtuple using a type class; my current effort is something like:
class VTuple ia ir a r | r -> a, a -> ia where vtuple :: (ia -> ir) -> IO (a -> r)
instance VTuple Int (IO ()) Int (Int, ()) where --vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ())) vtuple = undefined
instance VTuple ia ir a r => VTuple Int (ia -> ir) Int (a -> (Int, r)) where
--vtuple :: (Int -> ia -> ir) -> IO (Int -> a -> (Int, r)) vtuple = undefined
But this is problematic, since arrows creep in: For one argument (fine): vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ()))
vf :: IO (Int -> (Int, ())) vf = vtuple f
For two arguments (also fine): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int, ())))
vg :: IO (Int -> Int -> (Int, (Int, ()))) vg = vtuple g
For three (noooo!): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int -> (Int32, (Int32, ()))))) And so on. I've thought about it and it seems impossible to solve this problem -- you keep needing to ``split'' the function type one arrow further on. Is this a job for Template Haskell or is there a solution I'm missing here? Note that I'd also like to use types other than Int, but I don't think this is the primary complication here (touch wood). Any help much appreciated, thanks, Will

There's no (safe) way to go from
a -> IO b
to
IO (a -> b)
which is part of what vtuple does.
Consider
foo :: Int -> IO String
foo 0 = return "zero"
foo _ = launchMissles >> return "fired!"
How would you implement foo2 :: IO (Int -> String) with the same behavior?
You can't; you would somehow need to know the argument the function
was called at, and when it was going to be called, to implement foo2.
So I think you need a better specification!
-- ryan
On Wed, Aug 11, 2010 at 8:50 AM, Will Jones
Hi all,
I'm trying to write a function (I'll call it `vtuple' for lack of a better name) that returns a function that itself returns multiple arguments in the form of a tuple. For example:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-}
f :: Int -> IO () f = undefined
g :: Int -> Int -> IO () g = undefined
h :: Int -> Int -> Int -> IO () h = undefined
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ())))
I've tried to type vtuple using a type class; my current effort is something like:
class VTuple ia ir a r | r -> a, a -> ia where vtuple :: (ia -> ir) -> IO (a -> r)
instance VTuple Int (IO ()) Int (Int, ()) where --vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ())) vtuple = undefined
instance VTuple ia ir a r => VTuple Int (ia -> ir) Int (a -> (Int, r)) where
--vtuple :: (Int -> ia -> ir) -> IO (Int -> a -> (Int, r)) vtuple = undefined
But this is problematic, since arrows creep in:
For one argument (fine): vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ()))
vf :: IO (Int -> (Int, ())) vf = vtuple f
For two arguments (also fine): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int, ())))
vg :: IO (Int -> Int -> (Int, (Int, ()))) vg = vtuple g
For three (noooo!): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int -> (Int32, (Int32, ())))))
And so on. I've thought about it and it seems impossible to solve this problem -- you keep needing to ``split'' the function type one arrow further on. Is this a job for Template Haskell or is there a solution I'm missing here? Note that I'd also like to use types other than Int, but I don't think this is the primary complication here (touch wood).
Any help much appreciated, thanks, Will
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Ryan,
Thanks for the reply. The specification I've given is just to illustrate the
kind of relationship I'm trying to establish between the types of the
argument and the result. In reality the type of the argument function is
something a little more usable; you could generalise it with type families
vis:
class HasDual t where
type Dual t
class VTuple ia ir a r | r -> a where
vtuple :: (ia -> ir) -> IO (a -> r)
-- m is some monad.
instance (HasDual t, Dual t ~ dual) => VTuple dual (m a) t (t, ())
etc.
I hope that clears things up; to be honest I'm not sure it's relevant -- the
more I look at it the more I'm stumped.
Cheers,
Will
On Wed, Aug 11, 2010 at 7:08 PM, Ryan Ingram
There's no (safe) way to go from
a -> IO b
to
IO (a -> b)
which is part of what vtuple does.
Consider
foo :: Int -> IO String foo 0 = return "zero" foo _ = launchMissles >> return "fired!"
How would you implement foo2 :: IO (Int -> String) with the same behavior?
You can't; you would somehow need to know the argument the function was called at, and when it was going to be called, to implement foo2.
So I think you need a better specification!
-- ryan
Hi all,
I'm trying to write a function (I'll call it `vtuple' for lack of a better name) that returns a function that itself returns multiple arguments in the
On Wed, Aug 11, 2010 at 8:50 AM, Will Jones
wrote: form of a tuple. For example:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-}
f :: Int -> IO () f = undefined
g :: Int -> Int -> IO () g = undefined
h :: Int -> Int -> Int -> IO () h = undefined
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ())))
I've tried to type vtuple using a type class; my current effort is something like:
class VTuple ia ir a r | r -> a, a -> ia where vtuple :: (ia -> ir) -> IO (a -> r)
instance VTuple Int (IO ()) Int (Int, ()) where --vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ())) vtuple = undefined
instance VTuple ia ir a r => VTuple Int (ia -> ir) Int (a -> (Int, r)) where
--vtuple :: (Int -> ia -> ir) -> IO (Int -> a -> (Int, r)) vtuple = undefined
But this is problematic, since arrows creep in:
For one argument (fine): vtuple :: (Int -> IO ()) -> IO (Int -> (Int, ()))
vf :: IO (Int -> (Int, ())) vf = vtuple f
For two arguments (also fine): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int, ())))
vg :: IO (Int -> Int -> (Int, (Int, ()))) vg = vtuple g
For three (noooo!): vtuple :: (Int -> Int -> IO ()) -> IO (Int -> Int -> (Int, (Int -> (Int32, (Int32, ())))))
And so on. I've thought about it and it seems impossible to solve this problem -- you keep needing to ``split'' the function type one arrow further on. Is this a job for Template Haskell or is there a solution I'm missing here? Note that I'd also like to use types other than Int, but I don't think this is the primary complication here (touch wood).
Any help much appreciated, thanks, Will
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Will,
2010/8/11 Will Jones
I'm trying to write a function (I'll call it `vtuple' for lack of a better name) that returns a function that itself returns multiple arguments in the form of a tuple. For example:
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ())))
If we drop the IO (as pointed out by Ryan Ingram), vtuple seems weird - the only sensible function of the type "Int -> Int -> (Int, (Int, ()))" is a function that collects its arguments and returns them in a tuple, so it doesn't touch the input function g at all, it only cares about g's arity. Here's the solution:
vtuple f = eat (arity f) `mcomp` hListToTuple
class HListToTuple l r | l -> r where hListToTuple :: l -> r
instance HListToTuple HNil () where hListToTuple _ = ()
instance HListToTuple xs ys => HListToTuple (HCons x xs) (x,ys) where hListToTuple (HCons x xs) = (x,hListToTuple xs)
Rest of the code (functions eat, arity and mcomp) is presented here: http://paczesiowa.blogspot.com/2010/03/generalized-zipwithn.html Regards, Bartek Ćwikłowski

Will Jones wrote:
f :: Int -> IO () f = undefined
g :: Int -> Int -> IO () g = undefined
h :: Int -> Int -> Int -> IO () h = undefined
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ())))
I've tried to type vtuple using a type class; [...]
I've thought about it and it seems impossible to solve this problem -- you keep needing to ``split'' the function type one arrow further on.
So you need to use recursion to handle the arbitrary deeply nested arrows in the type of vtuple's argument. I tried it with type families, but I don't see a reason why functional dependencies should not work. {-# LANGUAGE FlexibleInstances, TypeFamilies #-} module VTupleWithTypeFamilies where We use two type families to handle the two places where the result type of vtuple changes for different argument types. type family F a type family G a r So the intention is that the type of vtuple is as follows. class VTuple a where vtuple :: a -> IO (G a (F a)) The base case: type instance F (IO ()) = () type instance G (IO ()) r = r instance VTuple (IO ()) where vtuple = undefined And the step case: type instance F (a -> b) = (a, F b) type instance G (a -> b) r = a -> G b r instance VTuple b => VTuple (a -> b) where vtuple = undefined A test case: f :: Int -> Bool -> Char -> Double -> IO () f = undefined test = do vt <- vtuple f return (vt 5 True 'x' 1.3) Testing it with ghci yields the following type for test, which looks good to me. test :: IO (Int, (Bool, (Char, (Double, ())))) HTH, Tillmann

Hi Tillmann, That's worked a treat -- thanks ever so much :) Will On Wed, Aug 11, 2010 at 7:50 PM, Tillmann Rendel < rendel@mathematik.uni-marburg.de> wrote:
Will Jones wrote:
f :: Int -> IO () f = undefined
g :: Int -> Int -> IO () g = undefined
h :: Int -> Int -> Int -> IO () h = undefined
vtuple f :: IO (Int -> (Int, ())) vtuple g :: IO (Int -> Int -> (Int, (Int, ())))
I've tried to type vtuple using a type class; [...]
I've thought about it and it seems impossible to solve this problem -- you keep needing to ``split'' the function type one arrow further on.
So you need to use recursion to handle the arbitrary deeply nested arrows in the type of vtuple's argument. I tried it with type families, but I don't see a reason why functional dependencies should not work.
{-# LANGUAGE FlexibleInstances, TypeFamilies #-} module VTupleWithTypeFamilies where
We use two type families to handle the two places where the result type of vtuple changes for different argument types.
type family F a type family G a r
So the intention is that the type of vtuple is as follows.
class VTuple a where vtuple :: a -> IO (G a (F a))
The base case:
type instance F (IO ()) = () type instance G (IO ()) r = r
instance VTuple (IO ()) where vtuple = undefined
And the step case:
type instance F (a -> b) = (a, F b) type instance G (a -> b) r = a -> G b r
instance VTuple b => VTuple (a -> b) where vtuple = undefined
A test case:
f :: Int -> Bool -> Char -> Double -> IO () f = undefined
test = do vt <- vtuple f return (vt 5 True 'x' 1.3)
Testing it with ghci yields the following type for test, which looks good to me.
test :: IO (Int, (Bool, (Char, (Double, ()))))
HTH, Tillmann
participants (4)
-
Bartek Ćwikłowski
-
Ryan Ingram
-
Tillmann Rendel
-
Will Jones