Re: [Haskell-cafe] Client-extensible heterogeneous types (Duck-typed variadic functions?)

On Oct 13, 2010, at 7:44 PM, Jacek Generowicz

On 2010 Oct 14, at 05:39, Brandon Moore wrote:
On Oct 13, 2010, at 7:44 PM, Jacek Generowicz
wrote:
On 2010 Oct 14, at 01:32, Evan Laforge wrote:
I think I'm starting too see what my problem is. I think it boils down to hankering for Duck Typing and variadic functions. I fully appreciate that passing functions is a wonderful and powerful technique for catering for variation, but Haskell's type system cramps my style by insisting that I can't put a (Banana -> Cake) in the same container as an (Octopus -> Truffles -> DogsBreakfast).
But the thing is, I don't use things like this, even in python.
Shame. They're damn useful :-)
How are you expecting to call the functions in that container? "for f in c: try: return f(*misc_args) except: pass"?
to_do = [(call, (AuntMabel,)), (buy, ([(12*kg, sugar), (6*bushel, wheat)])), (introduce, (Romeo, Juliet))]
for do,it in to_do: do(*it)
What is the point of doing that? If it's just to defer execution until that loop, you should just rely on lazy evaluation, or [IO ()].
There's more to it than that: The point is to treat combinations of functions and other data (which may or may not come from different sources, but are brought together to make a coherent whole) as entities which are allowed to reside in the same variable or the same container. Those other data might be the functions' arguments, or they might be other functions with which they are to be combined, or both. Here's an example where lazy evaluation isn't enough: def memoize(fn): cache = {} def memoized_fn(*args): if args not in cache: cache[args] = fn(*args) return cache[args] return memoized_fn You memoize a function once, but it will be given different arguments, many times, at a later time. But what should the type of fn be? What should the type of args be? In Python, I don't care, as long no type error occurs when they are combined thus: fn(*args) How do you let Haskell type check the combination of the types, rather than the individual types? My answer seems to be: define a variant type for holding the combinations. The problem with this is that the set of allowed combinations is closed at library compile time. I want it to remain open for extension. In Duck Typing this happens trivially.
If that's not the only thing you do, then the question is still how you know enough about the structure of values In the list to do anything useful with them.
There is a constraint on the *combination* of their types, while allowing the individual types to vary within that constraint. This constraint defines what I can do with them. Though, in practice, what I want to do with them defines the constraint. (I guess that looking at how memoization is done in Haskell might teach me something relevant.)
I suppose you haven't heard of parametricity theorems.
You suppose correctly :-)
In Haskell, values have no hair. If you don't know anything about the type of a values you can't inspect it. It's one of the major tools that helps type signatures contribute to the correctness of implementations. In Python, Java, and other similar languages there are lots of things you can do with unknown values - get a string representation, test for equality with another value, get the class it belongs to, etc.
So, we won't understand the point of your example without a little more information on what you do to those heterogeneous values, and how the program can tell which things to do wi which item,
Another example: Let's say I need an Int -> String. Both (fnA2 :: Banana -> String) . (fnA1:: Int -> Banana) and (fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion) will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place. The program can tell that it can combine them with (.) because the type of let (fn1, fn2) = pair in fn2 . fn1 is always Int -> String. The whole thing could be summarized by saying: Please type check the whole, not the individual parts; let me store the parts in the same place.
In Haskell it may be fun to turn on -XGADTs and write
Now you're just trying to burst my todo list, aren't you :-)
data DelayedApp result where Base :: a -> DelayedApp a App :: DelayedApp (a -> b) -> a -> DelayedApp b
but it turns out to be isomorphic to data DelayedResult r = DR a Nat - at least until you add some more data to the constructors.

Hi, Am Donnerstag, den 14.10.2010, 09:34 +0200 schrieb Jacek Generowicz:
Another example:
Let's say I need an Int -> String. Both
(fnA2 :: Banana -> String) . (fnA1:: Int -> Banana)
and
(fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion)
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place. The program can tell that it can combine them with (.) because the type of
let (fn1, fn2) = pair in fn2 . fn1
is always
Int -> String.
This is possible: {-# LANGUAGE ExistentialQuantification #-} data SplitFun a b = forall x. SplitFun (a -> x, x -> b) splitFuns :: [SplitFun Int String] splitFuns = [SplitFun (\n -> replicate n "hi", concat) ,SplitFun (show, id)] main = mapM_ putStrLn $ map (\(SplitFun (f1,f2)) -> f2 (f1 2)) splitFuns This prints: *Main> main hihi 2 Greetings, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

On 2010 Oct 14, at 09:54, Joachim Breitner wrote:
Hi,
Am Donnerstag, den 14.10.2010, 09:34 +0200 schrieb Jacek Generowicz:
Another example:
Let's say I need an Int -> String. Both
(fnA2 :: Banana -> String) . (fnA1:: Int -> Banana)
and
(fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion)
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place. The program can tell that it can combine them with (.) because the type of
let (fn1, fn2) = pair in fn2 . fn1
is always
Int -> String.
This is possible:
{-# LANGUAGE ExistentialQuantification #-}
Existential Quantification yet again! I see that its status in Haskell Prime is "None". Anybody care to hazard a guess as to the odds of its acceptance? Which implementations support it today ?
data SplitFun a b = forall x. SplitFun (a -> x, x -> b)
splitFuns :: [SplitFun Int String] splitFuns = [SplitFun (\n -> replicate n "hi", concat) ,SplitFun (show, id)]
And x might be a function type (with any number of arguments), so we get some variadicity for free! I hadn't thought of that. That's brilliant.
main = mapM_ putStrLn $ map (\(SplitFun (f1,f2)) -> f2 (f1 2)) splitFuns
This prints: *Main> main hihi 2
Brilliant. Thanks.

On 14 October 2010 08:34, Jacek Generowicz
Those other data might be the functions' arguments, or they might be other functions with which they are to be combined, or both.
You can represent these as existential packages. However, as Oleg shows you can always use skolemisation to eliminate the existential: http://okmij.org/ftp/Computation/Existentials.html This trick is basically what Brandon and Evan pointed out earlier when they suggested you replace the list :: [exists b. (b -> a, b)] with a list :: [a].
Here's an example where lazy evaluation isn't enough:
def memoize(fn): cache = {} def memoized_fn(*args): if args not in cache: cache[args] = fn(*args) return cache[args] return memoized_fn
You memoize a function once, but it will be given different arguments, many times, at a later time.
I'm not sure why you would use existentials for this. Isn't the type of memoized_fn just :: Ord a => (a -> b) -> a -> b? This doesn't deal with argument *lists* so you may have to curry/uncurry to get functions of a different arity to go through, but that is IMHO a reasonable requirement for Haskell, where multi-argument functions do not have special status. (In the absence of side effects, I can't see an obvious way to implement it without some way to enumerate the domain "a" though. Conal Elliot uses type classes to solve this issue, see http://hackage.haskell.org/package/MemoTrie, where memo :: HasTrie t => (t -> a) -> t -> a).
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place. The program can tell that it can combine them with (.) because the type of
But if the only operation you ever do on this pair is (.), you may as well skolemise and just store (fnA1 . fnA2) directly. What is the advantage of doing otherwise? Max

On 14 October 2010 08:56, Max Bolingbroke
But if the only operation you ever do on this pair is (.), you may as well skolemise and just store (fnA1 . fnA2) directly. What is the advantage of doing otherwise?
I forgot to mention that if you *really really* want to program with the type [exists b. (b -> a, b)] directly you can do it without defining a new data type to hold the existential package by using CPS style and making use of the logical law that not(exists a. P[a]) <==> forall a. not(P[a]): """ {-# LANGUAGE Rank2Types, ImpredicativeTypes #-} foo :: [forall res. (forall b. (b -> Bool, b) -> res) -> res] foo = [\k -> k (not, True), \k -> k ((<10), 5), \k -> k (uncurry (==), ("Hi", "Hi"))] main :: IO () main = print $ [k (\(f, x) -> f x) | k <- foo] """ I pass to each "k" in the "foo" list a continuation that consumes that item in the list (in this case, a function and its arguments) and returns a result of uniform type (in this case, Bool). Cheers, Max

On 2010 Oct 14, at 09:56, Max Bolingbroke wrote:
On 14 October 2010 08:34, Jacek Generowicz
wrote: Those other data might be the functions' arguments, or they might be other functions with which they are to be combined, or both.
You can represent these as existential packages. However, as Oleg shows you can always use skolemisation to eliminate the existential: http://okmij.org/ftp/Computation/Existentials.html
This trick is basically what Brandon and Evan pointed out earlier when they suggested you replace the list :: [exists b. (b -> a, b)] with a list :: [a].
Aaah. The link between the last two paragraphs is important. Thanks very much.
Here's an example where lazy evaluation isn't enough:
def memoize(fn): cache = {} def memoized_fn(*args): if args not in cache: cache[args] = fn(*args) return cache[args] return memoized_fn
You memoize a function once, but it will be given different arguments, many times, at a later time.
I'm not sure why you would use existentials for this. Isn't the type of memoized_fn just :: Ord a => (a -> b) -> a -> b?
I don't think so. The Python Duck Type of memoized_fn (and fn), expressed in Haskell syntax is a -> b | a -> b -> c | a -> b -> c -> d | etc. The type of memoize would be (a -> b) -> a -> b | (a -> b -> c) -> a -> b -> c | (a -> b -> c -> d) -> a -> b -> c -> d | etc. Which is the whole point of the * in *args. (Not sure why you specified Ord a. In Python you *would* need Hashable a,b,c,d.) Of course, you could argue that the type is (a -> b) -> a -> b | (a -> b -> c) -> (a, b) -> c | (a -> b -> c -> d) -> (a, b, c) -> d | etc. But does that change things significantly?
This doesn't deal with argument *lists* so you may have to curry/uncurry to get functions of a different arity to go through, but that is IMHO a reasonable requirement for Haskell, where multi-argument functions do not have special status.
I would argue that easily dealing with different arities is an important requirement of the "arithmetic test" motivating example.
(In the absence of side effects, I can't see an obvious way to implement it without some way to enumerate the domain "a" though. Conal Elliot uses type classes to solve this issue, see http://hackage.haskell.org/package/MemoTrie, where memo :: HasTrie t => (t -> a) -> t -> a).
Thanks for the heads-up.
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place. The program can tell that it can combine them with (.) because the type of
But if the only operation you ever do on this pair is (.), you may as well skolemise and just store (fnA1 . fnA2) directly. What is the advantage of doing otherwise?
(.) is not the *only* operation I will do. But I think that's a red herring. Regardless of what operation I will do, I think that the problem is that some of the components are known earlier than others. But I think that currying trivially solves this particular problem. So I think that, as you say, skolemisation will do the trick. Though I still haven't delved sufficiently into the article you cite at the top, to be sure that extensibility won't be curtailed by this approach. If it is, then existentials should do the job.

Jacek Generowicz
Let's say I need an Int -> String. Both
(fnA2 :: Banana -> String) . (fnA1:: Int -> Banana)
and
(fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion)
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place.
I think you can do this fairly easy with existentials, but..
The program can tell that it can combine them with (.)
..what else do you want to be able to do with them? (Because, if this is all, you'd just store the combination, no?). -k -- If I haven't seen further, it is by standing in the footprints of giants

On 2010 Oct 14, at 09:58, Ketil Malde wrote:
Jacek Generowicz
writes: Let's say I need an Int -> String. Both
(fnA2 :: Banana -> String) . (fnA1:: Int -> Banana)
and
(fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion)
will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in the same place.
I think you can do this fairly easy with existentials, but..
Yup, that's got through to me by now :-)
The program can tell that it can combine them with (.)
..what else do you want to be able to do with them? (Because, if this is all, you'd just store the combination, no?).
Yes, if the components became available at the same time. But they don't. However, I think that currying caters for this separate arrival time problem. Hmm, except that I would like to be able to store a collection of incomplete combinations and say "complete the combination by injecting random arguments of the relevant type". (This probably won't make sense unless you saw the "arithmetic test" motivating example.) And currying can't deal with this, as the *incomplete* combinations will have different types. But I suspect that Brandon's suggestion to use QuickCheck's Gen monad, could well help with this.
participants (5)
-
Brandon Moore
-
Jacek Generowicz
-
Joachim Breitner
-
Ketil Malde
-
Max Bolingbroke