
Greetings, I'm looking for dynamic dispatch on extensible sets of types. Here is a more detailed explanation of what I mean: ######################################################################## # Consider the following Python code as representative of something # you might see in Object-Orineted programs in all sorts of languages. # Create an abstract type from abc import ABCMeta, abstractmethod class Abstract: __metaclass__ = ABCMeta @abstractmethod def method(self): pass # Provide some reifications of the abstract type class Variant1(Abstract): def method(self): return "Variant 1 stuff" class Variant2(Abstract): def method(self): return "Variant 2 stuff" # Provide some utilities to process these data def heterogeneousProcessor(data): return [datum.method() for datum in data] # If you wrap all the above up in a library, clients can easily extend # it with their own new types which will still work within the # framework class ClientDefined(Abstract): def method(self): return "Client-defined stuff" heterogeneousContainer = [Variant1(), Variant2(), ClientDefined()] result = heterogeneousProcessor(heterogeneousContainer) ######################################################################## ------------------------------------------------------------------------ -- In Haskell, on the one hand, the heterogeneity is easily provided -- by algebraic data types data AbstractHeterogeneous = VariantHeterogeneous1 | VariantHeterogeneous2 methodHeterogeneous VariantHeterogeneous1 = "Variant 1 stuff" methodHeterogeneous VariantHeterogeneous2 = "Variant 2 stuff" heterogeneousProcessor dataa = [methodHeterogeneous datum | datum <- dataa] heterogeneousContainer = [VariantHeterogeneous1, VariantHeterogeneous2] resultHeterogeneous = heterogeneousProcessor heterogeneousContainer -- But in order to extend the set of variants, the client would have -- to modify the source code, changing the definiton of -- AbstractHeterogeneous and methodHeterogeneous, both of which belong -- to the library. ------------------------------------------------------------------------ -- On the other hand, the extensibility is easily provided by type -- classes -- Library code: class AbstractExtensible a where methodExtensible :: a -> String instance AbstractExtensible () where methodExtensible _ = "Variant 1 stuff" instance AbstractExtensible Char where methodExtensible _ = "Variant 2 stuff" -- Client extension: instance AbstractExtensible Int where methodExtensible _ = "Client-defined stuff" -- but in this case, there is no heterogeneity: you cannot create the -- equivalent of heterogeneousContainer above -- heterogeneousExtensibleContainer = ???? resultExtensible :: [String] resultExtensible = [methodExtensible (), methodExtensible 'a', methodExtensible (1::Int)] ------------------------------------------------------------------------ I can't see a Haskell solution which combines both of these orthogonal features without losing the benefits of the type system. (For example, I could create my own, weak, type system with tags to identify the type and maps to do the dispatch.) So my question is, what would be the Haskell approach to combining heterogeneity (as provided by variant (algebraic) types) with type-extensibility (as provided by type classes), without losing the benefits of Haskell's type system? I haven't looked into Template Haskell, but i guess that it is likely to provide a solution. But is there a solution in plain Haskell? Thanks.

To do this I would use dynamic types (via Data.Dynamic). There are more typeful ways to deal with heterogeneous structures[*], but if "clients can easily extend it with their own new types" you've pretty much defined what dynamic types solve. [*] See the HList papers and library and various solutions to the "expression problem".

[Sorry Stephen, didn't mean to take this off-list, hence the resend.] On 2010 Oct 12, at 14:31, Stephen Tetley wrote:
To do this I would use dynamic types (via Data.Dynamic).
Ah, yes, I've just stumbled upon these while trying to figure out what APPLY or FUNCALL would mean in Haskell.
There are more typeful ways to deal with heterogeneous structures[*], but if "clients can easily extend it with their own new types" you've pretty much defined what dynamic types solve.
Cool. I've just started experimenting with implementing the dynamism by holding functions (methods) alongside data in a variant type. I think I'll see what I learn by taking this a bit further, before digging into Data.Dynamic, but it's good to know there is some prior art to turn to in the long run. Many thanks. Reading the GHC docs on Data.Dynamic, I infer that Data.Dynamic is non- standard, but, in principle, portable to other implementations. Is that understanding correct?
[*] See the HList papers and library and various solutions to the "expression problem".
This seems to be extremely relevant too, though I think that I'll stick to my own experiment and Data.Dynamic to start with. Thanks very much.

On 12 October 2010 14:08, Jacek Generowicz
Reading the GHC docs on Data.Dynamic, I infer that Data.Dynamic is non-standard, but, in principle, portable to other implementations.
Is that understanding correct?
Yes - Data.Dynamic uses some GHC specifics but there are other "lightweight" encodings of dynamic types that I think just use existential types (which John Lato mentioned).

On Oct 12, 2010, at 4:24 AM, Jacek Generowicz wrote:
I can't see a Haskell solution which combines both of these orthogonal features without losing the benefits of the type system. (For example, I could create my own, weak, type system with tags to identify the type and maps to do the dispatch.)
Is there any particular reason why you want to actually to mirror Python code? I think that letting the programmer design domain specific control structures is rather the point of Haskell. Instead of relying on a one-sized fits all solution (which only really fits one kind of problem), you write your own. And it is typically easier to write the control structure than it is to implement it using the OO patterns, because of the notion of irreducible complexity. For example, the Factory pattern constructs a functor. You can write the essential semantics of doing this with a single Functor instance, instead of writing multiple classes which implement the semantics, while relying on implicit, and possibly ill-fitting semantics of method dispatch. The other OO patterns make this objection stronger. If you can write a UML diagram, you can turn it into a commutative diagram, and write less code by implementing its arrows. An OO class hierarchy is a very specific functor over objects (which attaches methods to objects). Haskell provides the Functor type class. Write your generic functions for specific functors: -- The varying "input" types. Will be attached to arbitrary values by the Functor instance. data A = A -- Variant 1 data B = B -- Variant 2 -- Some normalized Output type. data Output = Output -- The new control structure. data Attaches a = AttachesA A a | AttachesB B a -- Stick your conditional (varying) semantics in here. Corresponds to heterogeneousProcessor. -- The output presumably depends on whether A or B is attached, so this function is not equivalent -- to something of the form fmap (f :: a -> Output) (attaches :: Attaches a) runAttaches :: Attaches a -> Attaches Output runAttaches = undefined -- This corresponds roughly to heterogeneousProcessor(heterogeneousContainer): processedOutputs :: [Attaches a] -> [(Attaches Output)] processedOutputs as = fmap runAttaches as -- Functor instance. Now you have a way to treat an (Attaches a) value just like you would an a. (modulo calling fmap) instance Functor Attaches where fmap f (AttachesA A a) = (AttachesA A (f a)) fmap f (AttachesB B a) = (AttachesB B (f a))

On 2010 Oct 13, at 00:28, Alexander Solla wrote:
On Oct 12, 2010, at 4:24 AM, Jacek Generowicz wrote:
I can't see a Haskell solution which combines both of these orthogonal features without losing the benefits of the type system. (For example, I could create my own, weak, type system with tags to identify the type and maps to do the dispatch.)
Is there any particular reason why you want to actually to mirror Python code?
I don't want to: I merely have a situation in which an OO solution (not necessarily a good one) immediately springs to mind, while I didn't see any obvious way to do it in Haskell. (I am sure that this is my shortcoming, not Haskell's.) I included the Python example lest my question be too nebulous without it. I would be delighted to learn approaches which are completely different to anything offered by OO. In fact, for personal didactic purposes, being un-OO-like could even be considered to be a goal.
I think that letting the programmer design domain specific control structures is rather the point of Haskell.
While I don't, at the moment, understand exactly how this is the case, I do like the sound of it.
Instead of relying on a one-sized fits all solution (which only really fits one kind of problem), you write your own. And it is typically easier to write the control structure than it is to implement it using the OO patterns, because of the notion of irreducible complexity. For example, the Factory pattern constructs a functor. You can write the essential semantics of doing this with a single Functor instance, instead of writing multiple classes which implement the semantics, while relying on implicit, and possibly ill- fitting semantics of method dispatch. The other OO patterns make this objection stronger. If you can write a UML diagram, you can turn it into a commutative diagram, and write less code by implementing its arrows.
Lots of stuff that sounds fascinating, but whose detailed meaning is, at the moment, beyond my grasp. So let my start off by getting my teeth into your example code:
An OO class hierarchy is a very specific functor over objects (which attaches methods to objects).
This sounds very interesting, but, again, I'm having difficulty understanding *exactly* how that is.
Haskell provides the Functor type class. Write your generic functions for specific functors:
-- The varying "input" types. Will be attached to arbitrary values by the Functor instance.
data A = A -- Variant 1 data B = B -- Variant 2
-- Some normalized Output type. data Output = Output
-- The new control structure. data Attaches a = AttachesA A a | AttachesB B a
-- Stick your conditional (varying) semantics in here. Corresponds to heterogeneousProcessor.
Could you explain this a bit more? heterogeneousProcessor was extremely boring: its only interesting feature was the dot between "datum" and "method()" Here it is again: def heterogeneousProcessor(data): return [datum.method() for datum in data] I suspect that runAttaches is (potentially) a lot more interesting than that!
-- The output presumably depends on whether A or B is attached, so this function is not equivalent -- to something of the form fmap (f :: a -> Output) (attaches :: Attaches a)
runAttaches :: Attaches a -> Attaches Output runAttaches = undefined
-- This corresponds roughly to heterogeneousProcessor(heterogeneousContainer): processedOutputs :: [Attaches a] -> [(Attaches Output)] processedOutputs as = fmap runAttaches as
Would it be correct to say that runAttaches replaces Python's (Java's, C++'s etc.) dynamically dispatching dot, but also allows for a greater variety of behaviour? Alternatively, would it be interesting to compare and contrast runAttach to CLOS' generic functions, or even Clojure's arbitrary method selection mechanism?
-- Functor instance. Now you have a way to treat an (Attaches a) value just like you would an a. (modulo calling fmap) instance Functor Attaches where fmap f (AttachesA A a) = (AttachesA A (f a)) fmap f (AttachesB B a) = (AttachesB B (f a))
[ Aside: Briefly returning to my original question: I don't see how, if this were supplied in a library, it would allow clients to inject new entities into the framework. It all seems to hinge on the Attaches type, which would be defined in the library, and is not extensible without modifying the library source code (unless I'm missing something). Which doesn't diminish my desire to understand what you are saying, in the slightest. Can the set of variants usable in this framework be extended without modifying the original source? ] Coming back to your statement that "An OO class hierarchy is a very specific functor over objects (which attaches methods to objects)", how would we complete your code so that it implements this particular functor?

I admit I haven't read this whole thread in detail, but when I want something with an implementation that can vary dynamically I just pass a different function. Your original python example is equivalent to just passing strings in haskell, so lets add an argument: type Process = Int -> String heterogeneousProcessor :: [Process] -> [String] heterogeneousProcessor ps = [p 42 | p <- ps] -- or map ($42) ps variant1 n = "variant1 stuff " ++ show n -- etc. Now the user of your library can pass their own Process. I have a number of records in my program like "State { lookup_x :: Name -> Maybe X, lookup_y :: Name -> Maybe Y, do_something_important :: X -> Result }". They reduce dependencies by not exposing the (complicated) lookup details and types, and aid testing because I can just pass a state with a dummy 'do_something_important' (in my case, it's "update GUI", which is important to stub out for a test). This may be simpler than what you had in mind, but to narrow it down, could you provide a more specific example where this is inadequate?

On 2010 Oct 13, at 23:52, Evan Laforge wrote:
I admit I haven't read this whole thread in detail, but when I want something with an implementation that can vary dynamically I just pass a different function.
Of course.
Your original python example is equivalent to just passing strings in haskell,
Sure. The original example was kept trivial, thereby hiding the true problem.
so lets add an argument:
type Process = Int -> String
heterogeneousProcessor :: [Process] -> [String] heterogeneousProcessor ps = [p 42 | p <- ps] -- or map ($42) ps
variant1 n = "variant1 stuff " ++ show n -- etc.
Now the user of your library can pass their own Process.
Which works just fine, if all the different things I might wish to express can be expressed within (Int -> String) (or any other function type).
I have a number of records in my program like "State { lookup_x :: Name -> Maybe X, lookup_y :: Name -> Maybe Y, do_something_important :: X -> Result }". They reduce dependencies by not exposing the (complicated) lookup details and types, and aid testing because I can just pass a state with a dummy 'do_something_important' (in my case, it's "update GUI", which is important to stub out for a test).
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). I can get around this by creating a variant type which contains both of these (and any others I might ever need to use), but a) It's bloody tedious (compared to having to do exactly nothing in Duck Typing), b) The set of acceptable function types is not extensible by clients. Put another way, your X and Y types aren't flexible/large enough.
This may be simpler than what you had in mind, but to narrow it down, could you provide a more specific example where this is inadequate?
How about this? -- Imagine that I want to write a program which will help me practice -- basic arithmetic. -- At its core I might have the following three functions ask :: (Int, Int) -> String ask (a,b) = show a ++ " + " ++ show b answer :: (Int, Int) -> Int answer (a,b) = a + b check :: (Int, Int) -> String -> Bool check q ans = (read ans :: Int) == answer q -- which present the question, and check whether a given answer is -- correct. -- Now, imagine I've got addition down pat, and want to extend my -- repertoire to subtraction. I could introduce some flexibility into -- my core functions thus data Operation = Operation (Int -> Int -> Int) String ask' :: (Int, Int) -> Operation -> String ask' (a,b) (Operation _ sym) = show a ++ " " ++ sym ++ " " ++ show b answer' :: (Int, Int) -> Operation -> Int answer' (a,b) (Operation op _) = op a b check' :: (Int, Int) -> Operation -> String -> Bool check' q op ans = (read ans :: Int) == answer' q op -- Now my program can deal with any binary infix operations on -- Ints. But what if I now want to practice a unary operation -- (e.g. sqrt)? How about a binary prefix one (e.g. gdc) ? -- Maybe this is the way forward? data Question = BinaryInfix (Int -> Int -> Int) String Int Int | BinaryPrefix (Int -> Int -> Int) String Int Int | UnaryPrefix (Int -> Int) String Int ask'' :: Question -> String ask'' (BinaryInfix _ sym a b) = show a ++ " " ++ sym ++ " " ++ show b ask'' (BinaryPrefix _ sym a b) = sym ++ " " ++ show a ++ " " ++ show b ask'' (UnaryPrefix _ sym a) = sym ++ " " ++ show a answer'' :: Question -> Int answer'' (BinaryInfix op _ a b) = op a b answer'' (BinaryPrefix op _ a b) = op a b answer'' (UnaryPrefix op _ a) = op a check'' :: Question -> String -> Bool check'' q a = (read a :: Int) == answer'' q -- So far, so ... not too bad. -- I'm a little annoyed by the repetitive tedium of answer'': this -- will really wind me up when I get on to TernaryPrefix, -- QuaternaryPrefix etc. and I will hanker for something like Python's -- *args. -- Now, I go to a party and thoroughly impress my friends with my -- newly-acquired arithmetic wizardry. One thing leads to another and -- my program ends up in the hands of another soul or two, desperate -- to match my mental calculation powers: I acquire some users. And as -- every schoolboy knows, users are closely followed by feature -- requests. -- John wants to practice adding fractions. Cindy needs to learn to -- find all prime factors of a given number. -- Clearly -- -- check'' q a = (read a :: Int) == answer'' q -- -- won't cut the mustard any more. -- Now, I can't see any obvious reason why I can't just keep adding -- new constructors to Question, and corresponding patterns to ask, -- answer and check, but I'm a lazy bugger and want to palm this off -- onto the users by telling them that I am empowering them by giving -- them the ability to add new question types to the framework. -- How would I enable them to do this without them having to mess with -- the original source? -- More generally, I'd be happy to be given advice on how to structure -- this sort of program in Haskell.

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. How are you expecting to call the functions in that container? "for f in c: try: return f(*misc_args) except: pass"?
-- Imagine that I want to write a program which will help me practice -- basic arithmetic.
-- At its core I might have the following three functions
ask :: (Int, Int) -> String ask (a,b) = show a ++ " + " ++ show b
answer :: (Int, Int) -> Int answer (a,b) = a + b
check :: (Int, Int) -> String -> Bool check q ans = (read ans :: Int) == answer q
-- which present the question, and check whether a given answer is -- correct.
-- Now, imagine I've got addition down pat, and want to extend my -- repertoire to subtraction. I could introduce some flexibility into -- my core functions thus
data Operation = Operation (Int -> Int -> Int) String
ask' :: (Int, Int) -> Operation -> String ask' (a,b) (Operation _ sym) = show a ++ " " ++ sym ++ " " ++ show b
answer' :: (Int, Int) -> Operation -> Int answer' (a,b) (Operation op _) = op a b
check' :: (Int, Int) -> Operation -> String -> Bool check' q op ans = (read ans :: Int) == answer' q op
-- Now my program can deal with any binary infix operations on -- Ints. But what if I now want to practice a unary operation -- (e.g. sqrt)? How about a binary prefix one (e.g. gdc) ?
-- Maybe this is the way forward?
data Question = BinaryInfix (Int -> Int -> Int) String Int Int | BinaryPrefix (Int -> Int -> Int) String Int Int | UnaryPrefix (Int -> Int) String Int
Well, you're creating a little interpreter here. I agree with you that this is sometimes easier in a dynamic language because you can reuse the implementation language at runtime. In the extreme, in python, you can simply call eval() on the input string. I believe there are some packages on hackage that implement little languages that you might be able to reuse. But if you don't need a full-on language, one easy step is to wrap your haskell functions in a typechecker: apply1 f [x] = f x apply1 _ _ = throw hissy fit apply2 f [x, y] = f x y etc. Now you can put them all into one container. Yes, the family of apply functions may be a little tedious, and you may be able to use typeclass magic to automatically select the right apply function, but it doesn't seem like a big deal to me. If you want to extend this to different types, you just have to extend this in one more direction, and a typeclass definitely helps there.
-- I'm a little annoyed by the repetitive tedium of answer'': this -- will really wind me up when I get on to TernaryPrefix, -- QuaternaryPrefix etc. and I will hanker for something like Python's -- *args.
-- Now, I go to a party and thoroughly impress my friends with my -- newly-acquired arithmetic wizardry. One thing leads to another and -- my program ends up in the hands of another soul or two, desperate -- to match my mental calculation powers: I acquire some users. And as -- every schoolboy knows, users are closely followed by feature -- requests.
-- John wants to practice adding fractions. Cindy needs to learn to -- find all prime factors of a given number.
-- Clearly -- -- check'' q a = (read a :: Int) == answer'' q -- -- won't cut the mustard any more.
-- Now, I can't see any obvious reason why I can't just keep adding -- new constructors to Question, and corresponding patterns to ask, -- answer and check, but I'm a lazy bugger and want to palm this off -- onto the users by telling them that I am empowering them by giving -- them the ability to add new question types to the framework.
-- How would I enable them to do this without them having to mess with -- the original source?
Well, I guess you could find the bits of the question framework which are always the same regardless of how its extended, then think about what types those have. Then export that as a library so your users can put together their own program based on that. For example, if you always have a number of wrong answers and a number of right answers and print a scoreboard, then you have 'Int -> Int -> Scoreboard'. If the answers the users are expected to give vary (a single int, or a list of ints, or a string), then you can export some parsing primitives. Eventually, some invisible line is crossed and you have an EDSL for writing math tests. Your Question type could look like 'String -> Answer' and Answer = 'Wrong String | Right | ParseError String'.

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) (Actually, it is far more commonly used in Python in all sorts of function wrappers. But the general principle is the same: It's somebody else's problem to ensure they give me compatible data, but the type system won't grumble about the types being different; it will only complain when the result of bringing the types together doesn't make sense. All at run-time, of course.) The thing is, I can arrange for them to be compatible. Python won't be able to confirm this statically, but is it too much to ask of Haskell to have it figure out (statically) that all of (Int -> Bool, Int) (Banana -> Apple -> Orange -> Kiwi -> Bool, (Banana, Apple, Orange, Kiwi)) (Bool -> Bool -> Bool, (Bool, Bool)) can be combined to give Bool ? So, in my maths tester, I'm only ever going to stick together compatible versions of ask, answer and check, but in any given set, the types of the 3 functions will not be the same as those in any other set. At which point Haskell refuses to let me store them in the same container. (Without existential types, at least.)
data Question = BinaryInfix (Int -> Int -> Int) String Int Int | BinaryPrefix (Int -> Int -> Int) String Int Int | UnaryPrefix (Int -> Int) String Int
Well, you're creating a little interpreter here.
Yes, this can be viewed as an interpreter for maths testing language.
I agree with you that this is sometimes easier in a dynamic language because you can reuse the implementation language at runtime.
I don't think I'm looking for that in this case. I'm just asking to be allowed to stick both (A -> B -> X, (A, B)) and (C -> D -> E -> X, (C, D, E)) etc. in the same container, because, frankly, in the context in which they are used, they *are* the same.
In the extreme, in python, you can simply call eval() on the input string.
Aaaargh! No! For the love of all that is good, please! Nooooo! :-) But seriously, there's enough dynamism, introspection etc. in Python, that eval is almost completely avoidable. I've used it once, in a situation where faking up a Lisp macro turned out to be an order of magnitude simpler than the alternatives. But that's the only time I've been tempted. I find structured objects far easier and safer to manipulate than strings.
But if you don't need a full-on language, one easy step is to wrap your haskell functions in a typechecker:
apply1 f [x] = f x apply1 _ _ = throw hissy fit apply2 f [x, y] = f x y etc.
I would hope that the types could be checked statically, as I explained above.
Now you can put them all into one container. Yes, the family of apply functions may be a little tedious, and you may be able to use typeclass magic to automatically select the right apply function, but it doesn't seem like a big deal to me. If you want to extend this to different types, you just have to extend this in one more direction, and a typeclass definitely helps there.
Except that I now lose the ability to stick them all into the same container. (Unless I enable existential quantification.)
-- Now, I can't see any obvious reason why I can't just keep adding -- new constructors to Question, and corresponding patterns to ask, -- answer and check, but I'm a lazy bugger and want to palm this off -- onto the users by telling them that I am empowering them by giving -- them the ability to add new question types to the framework.
-- How would I enable them to do this without them having to mess with -- the original source?
Well, I guess you could find the bits of the question framework which are always the same regardless of how its extended, then think about what types those have. Then export that as a library so your users can put together their own program based on that. For example, if you always have a number of wrong answers and a number of right answers and print a scoreboard, then you have 'Int -> Int -> Scoreboard'. If the answers the users are expected to give vary (a single int, or a list of ints, or a string), then you can export some parsing primitives.
I'm pretty sure that you could never come up with a sufficiently large set of primitives. Even if you could, it seems like far too much work, given that the ability to store arbitrary (sets of co-operating) functions (which, together, always return the same types) in the same container, trivially provides you with full generality.
Eventually, some invisible line is crossed and you have an EDSL for writing math tests.
That is *exactly* where I am heading with this.
Your Question type could look like 'String -> Answer' and Answer = 'Wrong String | Right | ParseError String'.
Actually, I think it should be more like: Answer = ParseError String | Wrong String | NeitherWrongNorRightSoTryAgain String | Right where the fourth (erm, third) option would be used in situations such as: If I ask you for 50/100 and you reply 25/50, it's not wrong, but I'm not going to give you your cigar until you tell me that it's 1/2.

BTW Thanks: This discussion has helped me gain a better understanding of some of the mechanisms at work, which I really appreciate.

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)
As has been pointed out, simply write it like this: to_do = [call AuntMabel, buy [(12kg, sugar), (6 bushel, weat)], etc.] If they are monadic actions, you can call 'sequence_' on them when you want them to "happen". If not, you really just have a list.
The thing is, I can arrange for them to be compatible. Python won't be able to confirm this statically, but is it too much to ask of Haskell to have it figure out (statically) that all of
(Int -> Bool, Int) (Banana -> Apple -> Orange -> Kiwi -> Bool, (Banana, Apple, Orange, Kiwi)) (Bool -> Bool -> Bool, (Bool, Bool))
can be combined to give Bool ?
Yes, this sounds like an existential: data Boolable forall a. = Boolable (a -> Bool) But despite the fact that I've been keeping them in the back of my mind for years, I've never once come up with a place where one would actually be useful. I guess I just don't think that way.
I agree with you that this is sometimes easier in a dynamic language because you can reuse the implementation language at runtime.
I don't think I'm looking for that in this case. I'm just asking to be allowed to stick both
(A -> B -> X, (A, B))
and
(C -> D -> E -> X, (C, D, E))
etc. in the same container, because, frankly, in the context in which they are used, they *are* the same.
Maybe you should focus less on the particular implementation you want and more on the end result? If you start off saying "I want heterogenous lists" then you'll start off with a problem for haskell :)
In the extreme, in python, you can simply call eval() on the input string.
Aaaargh! No! For the love of all that is good, please! Nooooo! :-)
Well, yes, that's the extreme. My point was that when you call f(*args) you are also reusing the interpreter at runtime. The fact that values carry their types around at runtime is one example of this. Haskell doesn't have the interpreter around at runtime. But if you know exactly what parts of the interpreter you want, you can recover them, i.e. with Dynamic or by using 'hint' in the extreme. But keep in mind you are implementing an interpreter. BTW, I've used eval(s, {}) on a number of occasions when I wanted to parse ints or strings and didn't want to write my own parser. It doesn't seem that much different from 'read' in haskell.
apply1 f [x] = f x apply1 _ _ = throw hissy fit apply2 f [x, y] = f x y etc.
I would hope that the types could be checked statically, as I explained above.
They can. The strings coming in from the user, of course they can't, because they're not even known statically. The 'apply1' function, of course, is statically checked in that 'f' is required to be a function with a single string argument. Well, of the same type as the list passed.
Now you can put them all into one container. Yes, the family of apply functions may be a little tedious, and you may be able to use typeclass magic to automatically select the right apply function, but it doesn't seem like a big deal to me. If you want to extend this to different types, you just have to extend this in one more direction, and a typeclass definitely helps there.
Except that I now lose the ability to stick them all into the same container. (Unless I enable existential quantification.)
I meant to use typeclasses to make it easier to create a typechecking function, in the same way that 'apply[n]' creates a function that checks number of args. Then you can write 'apply1 f [x] = f (parse x)' and 'parse' will be 'parse_string' or 'parse_int' depending on the value 'f' expects. The end result is still a function '[String] -> Either ParseError Answer' and so can all go into the same container. You may even be able to overload 'apply' so it will dispatch on applyn depending on the arity. Then you just write [apply f, apply g, apply h] where 'f', 'g', and 'h' can all have different types. The bottom line is that you have to parse and typecheck the strings typed by the user at some point. In the python case, you reuse python's typechecker when you write f(*args). In the haskell case you have to check the types yourself, but typeclasses can probably make it pretty painless. If you want to reuse haskell's typechecker, then you can install hint and just eval the string directly. If you want to do something in between like python's f(*args)... well, I'm not aware of libraries that do that. You would have to construct an AST, unparse that to haskell code, and give that to hint. Sounds like a bother.
I'm pretty sure that you could never come up with a sufficiently large set of primitives. Even if you could, it seems like far too much work, given that the ability to store arbitrary (sets of co-operating) functions (which, together, always return the same types) in the same container, trivially provides you with full generality.
Could you provide a more concrete example? So far the simple example of int accepting functions with different arities is pretty easy to implement with a plain list, so maybe you could provide a bit of python or something that does what you want and would be harder with static types?
Eventually, some invisible line is crossed and you have an EDSL for writing math tests.
That is *exactly* where I am heading with this.
Well, good, haskell's supposed to be good at EDSLs :)
Your Question type could look like 'String -> Answer' and Answer = 'Wrong String | Right | ParseError String'.
Actually, I think it should be more like:
Answer = ParseError String | Wrong String | NeitherWrongNorRightSoTryAgain String | Right
Well sure, the point is that neither of these types are even polymorphic, let alone existential.

On 2010 Oct 14, at 09:19, Evan Laforge wrote:
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)
As has been pointed out, simply write it like this:
to_do = [call AuntMabel, buy [(12kg, sugar), (6 bushel, weat)], etc.]
Which works for this case, but not in general. For example here's the memoizer example I used in response to Brandon: 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 they are monadic actions, you can call 'sequence_' on them when you want them to "happen". If not, you really just have a list.
The thing is, I can arrange for them to be compatible. Python won't be able to confirm this statically, but is it too much to ask of Haskell to have it figure out (statically) that all of
(Int -> Bool, Int) (Banana -> Apple -> Orange -> Kiwi -> Bool, (Banana, Apple, Orange, Kiwi)) (Bool -> Bool -> Bool, (Bool, Bool))
can be combined to give Bool ?
Yes, this sounds like an existential:
data Boolable forall a. = Boolable (a -> Bool)
But despite the fact that I've been keeping them in the back of my mind for years, I've never once come up with a place where one would actually be useful. I guess I just don't think that way.
I think that Haskell allows so many completely different approaches to things, that serious Haskell programmers are essentially using completely different languages which share a small common core :-)
I agree with you that this is sometimes easier in a dynamic language because you can reuse the implementation language at runtime.
I don't think I'm looking for that in this case. I'm just asking to be allowed to stick both
(A -> B -> X, (A, B))
and
(C -> D -> E -> X, (C, D, E))
etc. in the same container, because, frankly, in the context in which they are used, they *are* the same.
Maybe you should focus less on the particular implementation you want and more on the end result? If you start off saying "I want heterogenous lists" then you'll start off with a problem for haskell :)
Of course. Please don't get the impression that I'm trying to fit things into my box and won't accept anything else. I'm here to learn. In the process of explaining what I mean in some particular case, I end up using language from which says that "I want this", but that only refers to the exploration of one particular approach. I am open to, and eagerly encourage, completely different suggestions.
Haskell doesn't have the interpreter around at runtime. But if you know exactly what parts of the interpreter you want, you can recover them, i.e. with Dynamic or by using 'hint' in the extreme.
Hint. Hmm. Embedding an interpreter into your code. I can imagine lots of interesting uses for this. But I don't think I want/need it in this case. Thanks for pointing it out, though.
apply1 f [x] = f x apply1 _ _ = throw hissy fit apply2 f [x, y] = f x y etc.
I would hope that the types could be checked statically, as I explained above.
They can. The strings coming in from the user, of course they can't,
Sure, but that's why we have a ParseError constructor in our Question type.
because they're not even known statically. The 'apply1' function, of course, is statically checked in that 'f' is required to be a function with a single string argument. Well, of the same type as the list passed.
But I feel rather cramped by x and y in apply2 being constrained to having the same type.
I'm pretty sure that you could never come up with a sufficiently large set of primitives. Even if you could, it seems like far too much work, given that the ability to store arbitrary (sets of co-operating) functions (which, together, always return the same types) in the same container, trivially provides you with full generality.
Could you provide a more concrete example? So far the simple example of int accepting functions with different arities is pretty easy to implement with a plain list,
Trivial, as long as you combine the components immediately. If you need to hold the components separately it becomes trickier. Specifically, you need to create a variadic wrapper for holding the components, at which point you lose extensibility. Again, I'm sure this isn't the only way, but it's the one that my inexperienced mind sees immediately.
so maybe you could provide a bit of python or something that does what you want and would be harder with static types?
Is the memoizer show above sufficient? If not I'll try to distil a minimal set of conflicting question types in the maths test example.
Eventually, some invisible line is crossed and you have an EDSL for writing math tests.
That is *exactly* where I am heading with this.
Well, good, haskell's supposed to be good at EDSLs :)
Your Question type could look like 'String -> Answer' and Answer = 'Wrong String | Right | ParseError String'.
Actually, I think it should be more like:
Answer = ParseError String | Wrong String | NeitherWrongNorRightSoTryAgain String | Right
Well sure, the point is that neither of these types are even polymorphic, let alone existential.
Yes, it's completely irrelevant to the meat of the discussion.

Jacek Generowicz
def memoize(fn): cache = {} def memoized_fn(*args): if args not in cache: cache[args] = fn(*args) return cache[args] return memoized_fn
Here's a simplified memoizer for Haskell: memoize :: (Integral t) => (t -> a) -> t -> a memoize f = ([f i | i <- [0..]]!!) . fromIntegral
But what should the type of fn be? What should the type of args be?
The args to fn must be of a type that is indexable by the memoizing structure. My example is simplistic, and will only memoize functions where the first argument is a integral, non-negative number, and it uses a list (with O(n) access), but you can probably improve it as you see fit. I think this will work for multi-parameter functions too, because of currying.
In Python, I don't care, as long no type error occurs when they are combined thus:
fn(*args)
In Haskell, the type of 'memoize g' is the same as 'g', so you don't have to care - the compiler cares for you. :-) Perhaps I'm missing something obvious? -k -- If I haven't seen further, it is by standing in the footprints of giants

On 2010 Oct 14, at 15:24, Ketil Malde wrote:
Jacek Generowicz
writes: def memoize(fn): cache = {} def memoized_fn(*args): if args not in cache: cache[args] = fn(*args) return cache[args] return memoized_fn
Here's a simplified memoizer for Haskell:
memoize :: (Integral t) => (t -> a) -> t -> a memoize f = ([f i | i <- [0..]]!!) . fromIntegral
This is a very cute snippet, but I think that its cuteness circumvents the whole point of the Python code, which was to demonstrate how heterogeneous duck-typed values can be used safely. The Python memoizer memoizes functions of *any* type: yours allows very limited heterogeneity, so I'm failing to see how it addresses the issue.
But what should the type of fn be? What should the type of args be?
The args to fn must be of a type that is indexable by the memoizing structure. My example is simplistic, and will only memoize functions where the first argument is a integral, non-negative number, and it uses a list (with O(n) access), but you can probably improve it as you see fit.
I think that now we're starting to concentrate on the memoizer in particular, rather that the more general issue that the memoizer was meant to exemplify.
I think this will work for multi-parameter functions too, because of currying.
In Python, I don't care, as long no type error occurs when they are combined thus:
fn(*args)
In Haskell, the type of 'memoize g' is the same as 'g', so you don't have to care - the compiler cares for you. :-)
Same in Python (except that the run-time cares for you, rather than the compiler). But in Haskell it sometimes also cares about fn and args separately, even when it shouldn't. My questions are about persuading it that it shouldn't.
Perhaps I'm missing something obvious?
I think that what you might have missed is that the only interesting type is that of fn(*args): that I don't care about the type of fn on its own, or the type of args on its own, but that together they make up whatever type is required. And that Haskell's type system gets in the way by insisting on checking the types of fn and args separately; while Python's gets out of the way, by only caring when the two are brought together and actually *used*. But maybe it is I who has missed you addressing this point. Either way, I think that pursuing the memoizer any further (interesting though it is in its own right) takes us too far off track. I think that the answer (well, one important answer) to my earlier question is: a) Existential Quantification allows you to do this. b) Skolemization allows you to do this without the Existential Quantification extension. From what little I've read around this subject, it seems that considerations similar to the ones I'm talking about are repeatedly used as motivations for Existential Quantification, so I'm pretty confident that I'm not completely full of crap; or if I am, then I'm in good company :-)

Thank you all for your contributions so far. Plenty of food for thought. I though I'd try to put it into practice and have a go at the motivating example I gave: essentially a EDSL for defining simple maths tests. I've included the beginnings of an attempt at the end. It started promisingly. As long as I stuck to binary operators over integers, everything went smoothly, and adding new question types was a joy. The first annoyance comes when adding the first unary operation into the set of questions. Then I was forced to duplicate make into make1 and make2: essentially identical functions, differing only in the number of arguments they take. This sort of copy-paste programming really annoys me, but I can live with it in this case, as the duplication will only be in one dimension (operator arity), and concerns only one function. But it all goes pear shaped as soon as I try to cater for questions dealing with fractions, for example: Now the type system requires me to duplicate all the question-making utilities and give them different names. I tried to mitigate this by using type classes but got walloped by the No Monomorphism Restriction, and so on, and so forth. Wherever I turned, the type system was getting in the way. Looking at it another way, I have the Question type which can contain a sufficient variety of questions, but providing a set of utilities for conveniently populating the type, without excessive code duplication, is something that I am unable to do with Haskell's type system getting in the way. But I take this to be my shortcoming rather than Haskell's, so I would appreciate advice on how to proceed with this exercise. Code follows. Thank you all. ====================================================== import System.IO (hFlush, stdout) data Result = Correct | Improve String | Huh String | Incorrect String deriving Show data Question = Question { ask :: String , answer :: String , check :: String -> Result } bool2result True = Correct bool2result False = Incorrect "" -- askers infix2 sym a b = show a ++ " " ++ sym ++ " " ++ show b prefix1 sym a = sym ++ " " ++ show a prefix2 sym a b = sym ++ " " ++ show a ++ " " ++ show b -- checkers chk correct given = bool2result $ read given == correct -- makers make1 op symbol asker checker a = Question ask (show answer) check where ask = asker symbol a answer = op a check = checker answer make2 op symbol asker checker a b = Question ask (show answer) check where ask = asker symbol a b answer = op a b check = checker answer -- question 'types' addition = make2 (+) "+" infix2 chk subtraction = make2 (-) "-" infix2 chk multiplication = make2 (*) "x" infix2 chk power = make2 (^) "^" infix2 chk square = (flip power) 2 cube = (flip power) 3 square' = make1 (^2) "square" prefix1 chk questions = [ addition 1 2 , subtraction 3 2 , multiplication 4 5 , square 3 , cube 3 ] test :: [Question] -> IO () test [] = return () test (q:qs) = do putStr $ ask q ++ " = " hFlush stdout reply <- getLine putStrLn $ show $ check q reply test qs main = test questions

Thank you all for your contributions so far. Plenty of food for thought.
I though I'd try to put it into practice and have a go at the motivating example I gave: essentially a EDSL for defining simple maths tests.
If you have a Python version that has other features you would like, you can send that too.
But it all goes pear shaped as soon as I try to cater for questions dealing with fractions, for example: Now the type system requires me to duplicate all the question-making utilities and give them different names. I tried to mitigate this by using type classes but got walloped by the No Monomorphism Restriction, and so on, and so forth. Wherever I turned, the type system was getting in the way.
NoMonomorphismRestriction is the one extension I used. I suppose I could have replaced def = beautiful combinators by def x = beautiful combinators x Dealing with curried functions of varying arity is one thing that does tend to be fairly annoying, but in this case addParam was possible. The rest was pretty straightforward, mostly avoiding duplication by making more specific helpers rather than more generic functions. {-# LANGUAGE NoMonomorphismRestriction #-} import System.IO (hFlush, stdout) data Result = Correct | Improve String | Huh String | Incorrect String deriving Show data Question = Question { ask :: String , answer :: String , check :: String -> Result } bool2result True = Correct bool2result False = Incorrect "" readCheckBy :: (Read a) => (a -> Bool) -> String -> Result readCheckBy pred str = case reads str of [(val,"")] -> bool2result (pred val) _ -> Huh "" readCheck :: (Read a, Eq a) => a -> String -> Result readCheck v s = readCheckBy (==v) s -- helpers value val prompt = Question prompt (show val) (readCheck val) infix2 op symbol a b = value (op a b) (unwords [show a, symbol, show b]) addParam :: (Show a) => (funTy -> String -> qty) -> (a -> funTy) -> String -> (a -> qty) addParam qmakr fun string v = qmakr (fun v) (string++" "++show v) prefix1 = addParam value prefix2 = addParam prefix1 prefix3 = addParam prefix2 -- question 'types' addition = infix2 (+) "+" subtraction = infix2 (-) "-" multiplication = infix2 (*) "x" power = infix2 (^) "^" square = (flip power) 2 cube = (flip power) 3 square' = prefix1 (^2) "square" pi1 = value pi "pi" pi2 = Question "pi" (show pi) (readCheckBy (\v -> abs (pi - v) / pi < 0.0001)) questions = [ addition 1 2 , subtraction 3 2 , multiplication 4 5 , square 3 , cube 3 , square' 7 , value 3.14 "pi" ] test :: Question -> IO () test q = do putStr $ ask q ++ " = " hFlush stdout reply <- getLine putStrLn $ show $ check q reply main = mapM_ test questions

Thanks Brandon! I really like the addParam utility,
value val prompt = Question prompt (show val) (readCheck val)
addParam :: (Show a) => (funTy -> String -> qty) -> (a -> funTy) -> String -> (a -> qty) addParam qmakr fun string v = qmakr (fun v) (string++" "++show v)
prefix1 = addParam value prefix2 = addParam prefix1 prefix3 = addParam prefix2
but my crusty and sleep-deprived brain is not really grokking the internal plumbing. So I'm trying to get to grips with a simpler variation on the same theme, and I'm still failing. I'm trying to write something along the lines of addArg :: nArgFn -> a -> nPlus1ArgFn addArg fn a = (a+) <---- fn where <---- = something which applies its right parameter to however many arguments it needs and feeds the result to the left parameter in order to allow me to say sum2 = (+) sum3 = addArg sum2 sum4 = addArg sum3 etc.

Jacek,
I haven't been following this thread in any detail, so I apologise if
I misunderstand your goal, but the ctm function in the polyToMonoid
library (which maps its parameters to any specified monoid) appears to
work in just this way.
It keeps consuming parameters until you hand it to the trm function to
deliver the final result. More documentation here:
http://hackage.haskell.org/packages/archive/polyToMonoid/0.1/doc/html/Data-P...
Kevin
On Oct 15, 11:38 am, Jacek Generowicz
Thanks Brandon!
I really like the addParam utility,
value val prompt = Question prompt (show val) (readCheck val)
addParam :: (Show a) => (funTy -> String -> qty) -> (a -> funTy) -> String -> (a -> qty) addParam qmakr fun string v = qmakr (fun v) (string++" "++show v)
prefix1 = addParam value prefix2 = addParam prefix1 prefix3 = addParam prefix2
but my crusty and sleep-deprived brain is not really grokking the internal plumbing.
So I'm trying to get to grips with a simpler variation on the same theme, and I'm still failing. I'm trying to write something along the lines of
addArg :: nArgFn -> a -> nPlus1ArgFn addArg fn a = (a+) <---- fn where <---- = something which applies its right parameter to however many arguments it needs and feeds the result to the left parameter
in order to allow me to say
sum2 = (+) sum3 = addArg sum2 sum4 = addArg sum3
etc.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On 2010 Oct 15, at 11:53, Kevin Jardine wrote:
Jacek,
I haven't been following this thread in any detail, so I apologise if I misunderstand your goal,
My goal (in this thread, at least) is to become a better Haskell programmer, rather than to actually write any specific program. Yes, there are specific goals cited as examples, but the overall purpose is the journey, rather than the destination: I want to learn to walk and to run, rather than to get anywhere, just yet.
but the ctm function in the polyToMonoid library (which maps its parameters to any specified monoid) appears to work in just this way.
Yes, I noticed your earlier announcement. Yes, I recognized that it's pertinent to my last message. Yes, I've stored it in my (rapidly growing) list of things that Haskell Cafe has thrown at me that I should look into more deeply :-) But my current short-term goal is to understand the plumbing in a function that Brandon supplied, and to acquire the ability to write this kind of function myself in my sleep, with my hands tied behind my back, while the walls are falling all around me. At the moment I'm not managing to write it at all :-(
It keeps consuming parameters until you hand it to the trm function to deliver the final result. More documentation here:
Sounds a bit like the scheme I use for curried functions in Python. Though in Python I also have the option of calling the function with zero arguments to indicate termination, rather than terminating more explicitly by giving it to a terminate function. (Curried functions in Python? Can you tell that there's a Haskell programmer dying to get out ? :-) I've thrown in an example at the end, in case anybody is interested.
http://hackage.haskell.org/packages/archive/polyToMonoid/0.1/doc/html/Data-P...
It's already in my bookmarks, but thanks for taking the time to bring
it to my attention.
=======
from functools import partial
def curry(fn):
"""Function decorator. Curries its argument. The curried version
collects all positional and keyword arguments it is given, until
it is called with an empty argument list, at which point it
applies the function to all the collected arguments."""
def curried_function(*args, **kwds):
if not (args or kwds):
return fn()
else:
it = partial(fn, *args, **kwds)
try:
it.__name__ = fn.__name__
except AttributeError:
pass
return curry(it)
try:
curried_function.__name__ = fn.__name__ + ' (curried)'
except AttributeError:
pass
curried_function.fn = fn
return curried_function
@curry
def collect(*args, **kwds):
return "I've collected: %s %s" % (args, kwds)
print collect #

On 2010 Oct 15, at 11:38, Jacek Generowicz wrote:
[...] So I'm trying to get to grips with a simpler variation on the same theme, and I'm still failing. I'm trying to write something along the lines of
addArg :: nArgFn -> a -> nPlus1ArgFn addArg fn a = (a+) <---- fn where <---- = something which applies its right parameter to however many arguments it needs and feeds the result to the left parameter
in order to allow me to say
sum2 = (+) sum3 = addArg sum2 sum4 = addArg sum3
etc.
-- OK, I've understood. -- You use an accumulator to keep track of what has been done with the -- arguments that have been seen so far, and addArg takes one more -- argument, each time, and mixes it in with what is already there. -- I smell a monad. addArgSum :: (Num a) => (a -> t) -> a -> a -> t addArgSum fn acc arg = fn (acc + arg) sum1' = id sum2' = addArgSum sum1' sum3' = addArgSum sum2' -- And here's a more general version. addArg combine fn acc arg = fn (combine arg acc) sum1 = id sum2 = addArg (+) sum1 sum3 = addArg (+) sum2 sum4 = addArg (+) sum3 -- But I don't really get why the following leads to complaints about -- infinite types. -- sumN n = iterate (addArg (+)) id

Using Brandon's code as a starting point (as it's far neater than mine), let's try asking some questions about fractions (I've included the whole program at the end). questions = [ addition 1 2, addition (1%2) (1%3) ] This works, but the the fractions are shown as "1 % 2" and to make it presentable to non-Haskellers, we have to change that to "1/2". In order to do this, I tried to replace show with my own version which I call view (in type class View). At this point I get ../arithmetic/hackBrandon.hs:63:23: Ambiguous type variable `t' in the constraints: `Num t' arising from the literal `1' at ../arithmetic/hackBrandon.hs:63:23 `View t' arising from a use of `addition' at ../arithmetic/hackBrandon.hs:63:14-25 `Read t' arising from a use of `addition' at ../arithmetic/hackBrandon.hs:63:14-25 Probable fix: add a type signature that fixes these type variable(s) My problem is that I don't see where I could add a type signature, but still keep addition :: a -> a -> Question polymorphic. ======= Here's the code demonstrating the problem ===== {-# LANGUAGE NoMonomorphismRestriction #-} import System.IO (hFlush, stdout) import Data.Ratio data Result = Correct | Improve String | Huh String | Incorrect String deriving Show data Question = Question { ask :: String , answer :: String , check :: String -> Result } bool2result True = Correct bool2result False = Incorrect "" readCheckBy :: (Read a) => (a -> Bool) -> String -> Result readCheckBy pred str = case reads str of [(val,"")] -> bool2result (pred val) _ -> Huh "" readCheck :: (Read a, Eq a) => a -> String -> Result readCheck v s = readCheckBy (==v) s -- customized show class View a where view :: a -> String instance View Int where view = show instance (Integral n) => View (Ratio n) where view = show -- helpers value val prompt = Question prompt (view val) (readCheck val) infix2 op symbol a b = value (op a b) (unwords [view a, symbol, view b]) addParam :: (View a) => (funTy -> String -> qty) -> (a -> funTy) -> String -> (a -> qty) addParam qmakr fun string v = qmakr (fun v) (string++" "++view v) prefix1 = addParam value prefix2 = addParam prefix1 prefix3 = addParam prefix2 -- question 'types' addition = infix2 (+) "+" questions = [ addition 1 2 , addition (1%2) (1%3) ] test :: Question -> IO () test q = do putStr $ ask q ++ " = " hFlush stdout reply <- getLine putStrLn $ show $ check q reply main = mapM_ test questions

On 2010 Oct 15, at 13:32, Jacek Generowicz wrote:
questions = [ addition 1 2, addition (1%2) (1%3) ]
My problem is that I don't see where I could add a type signature, but still keep
addition :: a -> a -> Question
polymorphic.
Well, OK, I could write addition 1 (2 :: Int) inside the question list, but that's rather ugly, and it would be immensely annoying to have to do this for every specific question. Is there anywhere else it could go ?

On Oct 13, 2010, at 2:18 PM, Jacek Generowicz wrote:
Is there any particular reason why you want to actually to mirror Python code?
I don't want to: I merely have a situation in which an OO solution (not necessarily a good one) immediately springs to mind, while I didn't see any obvious way to do it in Haskell.
Fair enough. :0)
Instead of relying on a one-sized fits all solution (which only really fits one kind of problem), you write your own. And it is typically easier to write the control structure than it is to implement it using the OO patterns, because of the notion of irreducible complexity. For example, the Factory pattern constructs a functor. You can write the essential semantics of doing this with a single Functor instance, instead of writing multiple classes which implement the semantics, while relying on implicit, and possibly ill-fitting semantics of method dispatch. The other OO patterns make this objection stronger. If you can write a UML diagram, you can turn it into a commutative diagram, and write less code by implementing its arrows.
Lots of stuff that sounds fascinating, but whose detailed meaning is, at the moment, beyond my grasp. So let my start off by getting my teeth into your example code:
An OO class hierarchy is a very specific functor over objects (which attaches methods to objects).
This sounds very interesting, but, again, I'm having difficulty understanding *exactly* how that is.
At a high level, a functor is a "thing" which attaches "things" to the elements of an algebra, in an algebraically compatible way. The functor laws express the compatibility conditions. Let's think about how non-duck typed OO systems are used (internally) at run-time. First, we have an algebra of objects. If we don't consider how the class hierarchy interacts with the objects, the objects are a lot like Haskell values. Basically, just locations in memory or another similar abstraction. Every object has a "principle class". We can model this by creating a functor that attaches a "class" to each location in memory. Some classes inherit from others. We can model this by creating a functor that attaches a list (or tree) of classes to each class (that we have attached to an object). Interpreting this model means searching for a class that has the method with the right name With these constructs, we can recreate dynamic method dispatch. In particular, a functor over a functor is a functor over the underlying functor's algebra. We can use "functor combinators" to make going 'up' and 'down' easier.
Haskell provides the Functor type class. Write your generic functions for specific functors:
-- The varying "input" types. Will be attached to arbitrary values by the Functor instance.
data A = A -- Variant 1 data B = B -- Variant 2
-- Some normalized Output type. data Output = Output
-- The new control structure. data Attaches a = AttachesA A a | AttachesB B a
-- Stick your conditional (varying) semantics in here. Corresponds to heterogeneousProcessor.
Could you explain this a bit more? heterogeneousProcessor was extremely boring: its only interesting feature was the dot between "datum" and "method()" Here it is again:
def heterogeneousProcessor(data): return [datum.method() for datum in data]
I suspect that runAttaches is (potentially) a lot more interesting than that!
It is as interesting as you want it to be. That's where you put the semantics for interpreting a in terms of the types A or B. For example, if A contained a list of named methods of the form (a -> Output), your runAttaches could search through the list, find the right one, and apply it.
-- The output presumably depends on whether A or B is attached, so this function is not equivalent-- to something of the form fmap (f :: a -> Output) (attaches :: Attaches a) runAttaches :: Attaches a -> Attaches Output runAttaches = undefined
-- This corresponds roughly to heterogeneousProcessor(heterogeneousContainer): processedOutputs :: [Attaches a] -> [(Attaches Output)] processedOutputs as = fmap runAttaches as
Would it be correct to say that runAttaches replaces Python's (Java's, C++'s etc.) dynamically dispatching dot, but also allows for a greater variety of behaviour?
Yes, that's right.
Alternatively, would it be interesting to compare and contrast runAttach to CLOS' generic functions, or even Clojure's arbitrary method selection mechanism?
I don't know, I'm not familiar with either. On the other hand, method dispatch is always pretty similar. The difference is the shape of the structure traversed to find the right method.
-- Functor instance. Now you have a way to treat an (Attaches a) value just like you would an a. (modulo calling fmap) instance Functor Attaches where fmap f (AttachesA A a) = (AttachesA A (f a)) fmap f (AttachesB B a) = (AttachesB B (f a))
[ Aside:
Briefly returning to my original question: I don't see how, if this were supplied in a library, it would allow clients to inject new entities into the framework. It all seems to hinge on the Attaches type, which would be defined in the library, and is not extensible without modifying the library source code (unless I'm missing something). Which doesn't diminish my desire to understand what you are saying, in the slightest.
As designed, we wouldn't be injecting new classes into the framework. We would be injecting the Attaches framework into other frameworks. This has "the same effect". For example: data SuperClass = SuperClass data Extension a = Extension SuperClass (Attaches a) instance Functor Extension where fmap f (Extension s a) = (Extension s (fmap f a)) If you wanted to maybe make this a little easier, you could refactor Attaches to something like: data Attaches a b = Attaches a b -- read: Attaches an a to a b and re-do runAttaches to dispatch over the a's. You might even want to use a type class to restrict the a's: class ClassLike class runAttaches :: (ClassLike class) => Attaches class a -> Attaches class Output If you're going to be doing lots of work with functors, you might want to check out "category-extras".

Jacek Generowicz
Could you explain this a bit more? heterogeneousProcessor was extremely boring: its only interesting feature was the dot between "datum" and "method()" Here it is again:
def heterogeneousProcessor(data): return [datum.method() for datum in data]
Typically we use an existential type for this:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
data A = A
data B = B
class HasFooMethod a where
foo :: a -> String
instance HasFooMethod A where
foo _ = "This is A's foo method"
instance HasFooMethod B where
foo _ = "This is B's foo method"
data SomeFoo = forall a . (HasFooMethod a) => SomeFoo a
printFoo :: SomeFoo -> IO ()
printFoo (SomeFoo x) = putStrLn $ foo x
----------------------------------------------------------------------
main :: IO ()
main = do
let foos = [SomeFoo A, SomeFoo B, SomeFoo A]
mapM_ printFoo foos
Running main:
*Main> main
This is A's foo method
This is B's foo method
This is A's foo method
There is more information about the different ways of doing this kind of
thing in Haskell in the OOHaskell paper:
http://homepages.cwi.nl/~ralf/OOHaskell/
Unfortunately, this model of programming is a little awkward in Haskell
which is why (for the most part) it isn't used as much as it could or
should be. N.B. that the Control.Exception module from the standard
library (from GHC 6.8 on at least) uses this technique to provide
extensible exceptions.
Hope this helps,
G.
--
Gregory Collins

[Gregory: Sorry about duplicate, accidentally took it off-list.] On 2010 Oct 14, at 09:46, Gregory Collins wrote:
Jacek Generowicz
writes: Could you explain this a bit more? heterogeneousProcessor was extremely boring: its only interesting feature was the dot between "datum" and "method()" Here it is again:
def heterogeneousProcessor(data): return [datum.method() for datum in data]
Typically we use an existential type for this:
{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE RankNTypes #-}
data A = A data B = B
class HasFooMethod a where foo :: a -> String
instance HasFooMethod A where foo _ = "This is A's foo method"
instance HasFooMethod B where foo _ = "This is B's foo method"
data SomeFoo = forall a . (HasFooMethod a) => SomeFoo a
printFoo :: SomeFoo -> IO () printFoo (SomeFoo x) = putStrLn $ foo x
---------------------------------------------------------------------- main :: IO () main = do let foos = [SomeFoo A, SomeFoo B, SomeFoo A]
mapM_ printFoo foos
Running main:
*Main> main This is A's foo method This is B's foo method This is A's foo method
Yes, I've now understood that ExistentialQuantification can help with this, and I've even got as far coming up with almost exactly this example of its use. But it's good to have confirmation that I'm doing it right. So thanks for this code sample.
There is more information about the different ways of doing this kind of thing in Haskell in the OOHaskell paper: http://homepages.cwi.nl/~ralf/OOHaskell/
Abstract looks good. On the one hand I want to explore how Haskell allows me to do things in a way that doesn't resemble OO at all. On the other, it's good to see how OO-like things might be done in Haskell.
Unfortunately, this model of programming is a little awkward in Haskell which is why (for the most part) it isn't used as much as it could or should be. N.B. that the Control.Exception module from the standard library (from GHC 6.8 on at least) uses this technique to provide extensible exceptions.
Hope this helps,
Yes. Thanks. Only problem is, that you (plural) have, in about half-a-dozen responses, given me sufficient food for thought to occupy my brain for the next couple of months! :-)

On 14 October 2010 10:15, Jacek Generowicz
[Gregory: Sorry about duplicate, accidentally took it off-list.]
On 2010 Oct 14, at 09:46, Gregory Collins wrote: There is more information about the different ways of doing this kind of thing in Haskell in the OOHaskell paper: http://homepages.cwi.nl/~ralf/OOHaskell/
Abstract looks good. On the one hand I want to explore how Haskell allows me to do things in a way that doesn't resemble OO at all. On the other, it's good to see how OO-like things might be done in Haskell.
I find Section 2 in "Unfolding Abstract Datatypes" by Jeremy Gibbons a more pleasant example of existentials as its limited to abstract datatypes rather than fully blown OO (personally I don't particularly agree that the OO-Haskell style should be used more...) http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/adt.pdf A typographical note, if you want to run the code in the paper /backwards E/ should be replaced with /forall/.
participants (9)
-
Alexander Solla
-
Brandon Moore
-
Evan Laforge
-
Gregory Collins
-
Jacek Generowicz
-
Jacek Generowicz
-
Ketil Malde
-
Kevin Jardine
-
Stephen Tetley