[Haskell-cafe] Client-extensible heterogeneous types

7 views
Skip to first unread message

Jacek Generowicz

unread,
Oct 12, 2010, 7:24:54 AM10/12/10
to haskel...@haskell.org
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.

_______________________________________________
Haskell-Cafe mailing list
Haskel...@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Stephen Tetley

unread,
Oct 12, 2010, 8:31:28 AM10/12/10
to haskel...@haskell.org
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".

Jacek Generowicz

unread,
Oct 12, 2010, 9:08:30 AM10/12/10
to Stephen Tetley, haskel...@haskell.org
[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.

John Lato

unread,
Oct 12, 2010, 9:44:04 AM10/12/10
to Jacek Generowicz, haskel...@haskell.org
From: Jacek Generowicz <jacek.ge...@cern.ch>


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?

It's not plain Haskell, but I'm surprised nobody mentioned the ExistentialQuantification extension, which unless I'm missing something provides exactly what you want.

John

Stephen Tetley

unread,
Oct 12, 2010, 10:12:44 AM10/12/10
to haskel...@haskell.org
On 12 October 2010 14:08, Jacek Generowicz <Jacek.Ge...@cern.ch> wrote:

> 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).

Alexander Solla

unread,
Oct 12, 2010, 6:28:32 PM10/12/10
to haskell-cafe Cafe

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))



Jacek Generowicz

unread,
Oct 13, 2010, 5:18:29 PM10/13/10
to Alexander Solla, haskell-cafe Cafe

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?

Evan Laforge

unread,
Oct 13, 2010, 5:52:14 PM10/13/10
to Jacek Generowicz, haskell-cafe Cafe
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?

Jacek Generowicz

unread,
Oct 13, 2010, 7:07:29 PM10/13/10
to Evan Laforge, haskell-cafe Cafe

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.

Jacek Generowicz

unread,
Oct 13, 2010, 7:29:25 PM10/13/10
to John Lato, haskel...@haskell.org

On 2010 Oct 12, at 15:44, John Lato wrote:

> It's not plain Haskell, but I'm surprised nobody mentioned the
> ExistentialQuantification extension, which unless I'm missing
> something provides exactly what you want.

Yes, it does appear to be *exactly* what I want.

Thanks.

(Now, how about those HLists?)

Evan Laforge

unread,
Oct 13, 2010, 7:32:59 PM10/13/10
to Jacek Generowicz, haskell-cafe Cafe
> 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"?

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'.

Jacek Generowicz

unread,
Oct 13, 2010, 8:44:31 PM10/13/10
to Evan Laforge, haskell-cafe Cafe

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.

Jacek Generowicz

unread,
Oct 13, 2010, 8:48:00 PM10/13/10
to Evan Laforge, haskell-cafe Cafe
BTW Thanks: This discussion has helped me gain a better understanding
of some of the mechanisms at work, which I really appreciate.

Alexander Solla

unread,
Oct 13, 2010, 9:01:09 PM10/13/10
to haskell-cafe Cafe

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".

Brandon Moore

unread,
Oct 13, 2010, 11:27:08 PM10/13/10
to Jacek Generowicz, haskell-cafe Cafe
If you just want instances of questions you can keep it simple. How about something isomorphic to

data Instance = Instance { question : String, answer : String, check : String -> Bool }

You could make helper functions similar to your old code, like

addition : (Int , Int) -> Instance

You might handle problem families by taking a random number generator, or maybe using QuickCheck's Gen monad.

easyMultiplication : Gen Instance

Brandon Moore

unread,
Oct 13, 2010, 11:39:46 PM10/13/10
to Jacek Generowicz, haskell-cafe Cafe

On Oct 13, 2010, at 7:44 PM, Jacek Generowicz <jacek.ge...@cern.ch> 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 ()].

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.

If you just want to be able to inspect them interactively, you should ask about support for inspecting thunks in the ghci debugger.

I suppose you haven't heard of parametricity theorems. 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,

In Haskell it may be fun to turn on -XGADTs and write

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.

Evan Laforge

unread,
Oct 14, 2010, 3:19:08 AM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
>> 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.

Jacek Generowicz

unread,
Oct 14, 2010, 3:26:50 AM10/14/10
to Brandon Moore, haskell-cafe Cafe

On 2010 Oct 14, at 05:27, Brandon Moore wrote:

> If you just want instances of questions you can keep it simple. How
> about something isomorphic to
>
> data Instance = Instance { question : String, answer : String,
> check : String -> Bool }

At first blush, I hated all those Strings hiding the actual type
information. Thinking about it a bit more, I think that's exactly
right: when crossing the interface to the outside world, all data have
type String: the user reads Strings and types back Strings.

A variety of things happens behind those strings, but at the
interface, they're all strings.

> You could make helper functions similar to your old code, like
>
> addition : (Int , Int) -> Instance
>
> You might handle problem families by taking a random number
> generator, or maybe using QuickCheck's Gen monad.

Oh, I love the idea of Using QuickGen's Gen for this purpose! (And it
would finally give me the incentive to get to understand the beast
properly.)

Jacek Generowicz

unread,
Oct 14, 2010, 3:34:18 AM10/14/10
to Brandon Moore, haskell-cafe Cafe

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 :-)

Gregory Collins

unread,
Oct 14, 2010, 3:46:01 AM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
Jacek Generowicz <jacek.ge...@cern.ch> 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

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 <gr...@gregorycollins.net>

Joachim Breitner

unread,
Oct 14, 2010, 3:54:50 AM10/14/10
to haskel...@haskell.org
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: ma...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
JID: nom...@joachim-breitner.de | http://www.joachim-breitner.de/
Debian Developer: nom...@debian.org

signature.asc

Max Bolingbroke

unread,
Oct 14, 2010, 3:56:07 AM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
On 14 October 2010 08:34, Jacek Generowicz <jacek.ge...@cern.ch> 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].

> 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

Ketil Malde

unread,
Oct 14, 2010, 3:58:40 AM10/14/10
to haskell-cafe Cafe
Jacek Generowicz <jacek.ge...@cern.ch> 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..

> 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

Max Bolingbroke

unread,
Oct 14, 2010, 4:25:57 AM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
On 14 October 2010 08:56, Max Bolingbroke <batters...@hotmail.com> wrote:
> 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,

Jacek Generowicz

unread,
Oct 14, 2010, 4:34:21 AM10/14/10
to Evan Laforge, haskell-cafe Cafe

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

unread,
Oct 14, 2010, 5:15:40 AM10/14/10
to Gregory Collins, haskell-cafe Cafe
[Gregory: Sorry about duplicate, accidentally took it off-list.]

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! :-)

Jacek Generowicz

unread,
Oct 14, 2010, 5:26:35 AM10/14/10
to Joachim Breitner, haskel...@haskell.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.

Jacek Generowicz

unread,
Oct 14, 2010, 5:56:20 AM10/14/10
to Max Bolingbroke, haskell-cafe Cafe

On 2010 Oct 14, at 09:56, Max Bolingbroke wrote:

> On 14 October 2010 08:34, Jacek Generowicz
> <jacek.ge...@cern.ch> 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

unread,
Oct 14, 2010, 6:09:40 AM10/14/10
to Ketil Malde, haskell-cafe Cafe

On 2010 Oct 14, at 09:58, Ketil Malde wrote:

> Jacek Generowicz <jacek.ge...@cern.ch> 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.

Ketil Malde

unread,
Oct 14, 2010, 9:24:34 AM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
Jacek Generowicz <jacek.ge...@cern.ch> 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

> 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

Stephen Tetley

unread,
Oct 14, 2010, 9:41:11 AM10/14/10
to haskell-cafe Cafe
On 14 October 2010 10:15, Jacek Generowicz <Jacek.Ge...@cern.ch> wrote:
> [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/.

Jacek Generowicz

unread,
Oct 14, 2010, 11:02:15 AM10/14/10
to Ketil Malde, haskell-cafe Cafe

On 2010 Oct 14, at 15:24, Ketil Malde wrote:

> Jacek Generowicz <jacek.ge...@cern.ch> 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 :-)

Jacek Generowicz

unread,
Oct 14, 2010, 3:37:16 PM10/14/10
to haskell-cafe Cafe
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

Brandon Moore

unread,
Oct 14, 2010, 6:07:27 PM10/14/10
to Jacek Generowicz, haskell-cafe Cafe
> 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

Jacek Generowicz

unread,
Oct 15, 2010, 5:38:43 AM10/15/10
to Brandon Moore, haskell-cafe Cafe
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.

Kevin Jardine

unread,
Oct 15, 2010, 5:53:24 AM10/15/10
to haskel...@haskell.org
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-PolyToMonoid.html

Kevin

On Oct 15, 11:38 am, Jacek Generowicz <jacek.generow...@cern.ch>
wrote:

> Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Jacek Generowicz

unread,
Oct 15, 2010, 6:46:04 AM10/15/10
to Kevin Jardine, haskel...@haskell.org

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-PolyToMonoid.html

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 # <function collect (curried) at 0x712db0>
print collect(1) # <function collect (curried) at 0x712d30>
print collect(1)(2,3,c=4) # <function collect (curried) at 0x712bf0>
print collect(1)(2,3,c=4)() # I've collected: (1, 2, 3) {'c': 4}

Jacek Generowicz

unread,
Oct 15, 2010, 7:32:06 AM10/15/10
to Brandon Moore, haskell-cafe Cafe
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)

Jacek Generowicz

unread,
Oct 15, 2010, 7:56:24 AM10/15/10
to haskell-cafe Cafe

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 ?

Jacek Generowicz

unread,
Oct 15, 2010, 9:40:06 AM10/15/10
to haskell-cafe Cafe

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

Reply all
Reply to author
Forward
0 new messages