Re: Another fold question

2003-11-05 Thread Derek Elkins
On Thu, 06 Nov 2003 04:27:31 +
"Patty Fong" <[EMAIL PROTECTED]> wrote:

> Having struglled over this for the better part of a day and only
> becoming more frustrated the more i try to understand it, i once again
> seek help :)
> 
> I understand how basic folds work, i.e foldr replaces (:) with some 
> parameter and [] by another i.e
> foldr (+) 0 [1,2,3] becomes 1+(2+(3+0))
> 
> I also understand how to write my own fold function. What i don't
> understand quite is how to use them. given this data type and this
> fold function i wrote:
> 
> data Music
>   = Note Pitch Octave Duration
>   | Silence Duration
>   | PlayerPar Music Music
>   | PlayerSeq Music Music
>   | Tempo (Ratio Int) Music
> data Pitch = Cf | C | Cs
> type Octave = Int
> type Duration = Ratio Int
> 
> foldMusic :: (Pitch -> Octave -> Duration -> a)
>   -> (Duration -> a)
>   -> (a -> a -> a)
>   -> (a -> a -> a)
>   -> (Ratio Int -> a -> a)
>   -> Music
>   -> a
> 
> foldMusic n _ _ _ _ (Note pitch octive duration) = n pitch octive
> duration foldMusic _ s _ _ _ (Silence duration) = s duration
> foldMusic n s p1 p2 t (PlayerPar partOne partTwo) = p1 (foldMusic n s
> p1 p2 t partOne)(foldMusic n s p1 p2 t partTwo)
> foldMusic n s p1 p2 t (PlayerPar partA partB) = p2 (foldMusic n s p1
> p2 t partA)(foldMusic n s p1 p2 t partB)
> foldMusic n s p1 p2 t (Tempo rate part) = t rate (foldMusic n s p1 p2
> t part)
> 
> I understand that when i use the foldMusic function i need to pass it
> 5 parameters.  given the type signiature, why can i pass (+) as a
> parameter for p1 but not for n, what determines what can be passed as
> a parameter, because they all have the return type a??

Because (+) :: Num a => a -> a -> a and that's definitely not Pitch ->
Octave -> Duration -> a.  But all functions will need to return
the same type.  Once you apply all five functions to foldMusic the
result will be a function with type Music -> a (well, what a was bound
to).  Since that function can be applied to any particular constructor
of Music then the function that will replace a particular constructor
needs to return the same type as the others.

> I attempted to create a function that utilises the foldMusic function
> that counts the number of notes:
> 
> count_notes :: Music -> Integer
> count_notes = foldMusic (\_-> \_ -> \_ -> 1) (\_ -> 0) (+) (+) (\_ ->
> \_ -> 0)

You can use \_ _ _ -> 0 instead of nested lambdas.

> it appears to work, i think. Yet i'm still not certain of how it does
> so.
> 
> This confuses me,
> Is there anyway to represent other fold functions in a tree like 
> representation as foldr (+) 0 would appear as such?
> +
>1 \
>   +
>  2 \
> +
>3 \
>   0

All datatypes can be represented in a tree-like (graph-like actually)
way and folds follow the structure of the type(s) that they fold over. 
So for Music a particular instance might look like,

Tempo (2%1)
|   
 PlayerPar
/ \
   PlayerSeqNote ...
  /  \
Note ...   Silence (3%4)
folds in general work from the "leaves" of the datatype to the root. 
Or another way, for more mathematically inclined people, is that folds
follow (are) the induction principle of the datatype, it works from base
case to inductive cases.  A still third way of thinking about it is that
a datastructure is an AST (abstract syntax tree) for some language and
that a fold (applied to it's parameters) is an intepreter for that
language.  So for example, you likely want to play the music so you
might have a function like,
playMusic = foldMusic playNote pause playPar playSeq changeTempo

playMusic then interprets a Music data structure as sound.  Another
"interpreter" you might want is something that lays out the music, so
you might have,
printMusic = foldMusic drawNote 
   drawRest
   overlapDrawing
   nextBar
   drawTimeSignature
printMusic interprets a Music data structure as say a pdf of sheet
music.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-05 Thread ajb
G'day all.

Quoting Patty Fong <[EMAIL PROTECTED]>:

> I also understand how to write my own fold function. What i don't understand
> quite is how to use them. given this data type and this fold function i
> wrote:
> 
> data Music
>   = Note Pitch Octave Duration
>   | Silence Duration
>   | PlayerPar Music Music
>   | PlayerSeq Music Music
>   | Tempo (Ratio Int) Music
> data Pitch = Cf | C | Cs
> type Octave = Int
> type Duration = Ratio Int

I know this doesn't answer your question, but for this example, it might
be easier to use some kind of iterator.  In this example:

getNotes :: Music -> [Music]
getNotes n@(Note _ _ _) = [n]
getNotes (PlayerPar m1 m2) = getNotes m1 ++ getNotes m2
-- etc etc

count_notes = length . getNotes

See http://haskell.org/hawiki/IterationPattern for some ideas.
 
Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-05 Thread Thomas L. Bevan
patty,

what you have written is not a fold. A fold operates over a list. There is no 
list in your code, only some sort of tree structure.

> foldMusic :: (Pitch -> Octave -> Duration -> a)
>   -> (Duration -> a)
>   -> (a -> a -> a)
>   -> (a -> a -> a)
>   -> (Ratio Int -> a -> a)
>   -> Music
>   -> a
>

> I understand that when i use the foldMusic function i need to pass it 5
> parameters.  given the type signiature, why can i pass (+) as a parameter
> for p1 but not for n, what determines what can be passed as a parameter,
> because they all have the return type a??
 The first argument of your function is of type, (Duration -> a)
(+) has the type, a -> a -> a, so it is nothing like the first argument.

countNotes :: Music -> Int

countNotes Silence _ =  0 
countNotes Note_ =  1
countNotes PlayerPar m1 m2 =  (countNotes m1) + (countNotes m2)
countNotes PlayerSeq m1 m2 =   (countNotes m1) + (countNotes m2)
countNotes Tempo _ m =  countNotes m

Tom
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Another fold question

2003-11-05 Thread Patty Fong
Having struglled over this for the better part of a day and only becoming 
more frustrated the more i try to understand it, i once again seek help :)

I understand how basic folds work, i.e foldr replaces (:) with some 
parameter and [] by another i.e
foldr (+) 0 [1,2,3] becomes 1+(2+(3+0))

I also understand how to write my own fold function. What i don't understand 
quite is how to use them. given this data type and this fold function i 
wrote:

data Music
= Note Pitch Octave Duration
| Silence Duration
| PlayerPar Music Music
| PlayerSeq Music Music
| Tempo (Ratio Int) Music
data Pitch = Cf | C | Cs
type Octave = Int
type Duration = Ratio Int
foldMusic :: (Pitch -> Octave -> Duration -> a)
-> (Duration -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (Ratio Int -> a -> a)
-> Music
-> a
foldMusic n _ _ _ _ (Note pitch octive duration) = n pitch octive duration
foldMusic _ s _ _ _ (Silence duration) = s duration
foldMusic n s p1 p2 t (PlayerPar partOne partTwo) = p1 (foldMusic n s p1 p2 
t partOne)(foldMusic n s p1 p2 t partTwo)
foldMusic n s p1 p2 t (PlayerPar partA partB) = p2 (foldMusic n s p1 p2 t 
partA)(foldMusic n s p1 p2 t partB)
foldMusic n s p1 p2 t (Tempo rate part) = t rate (foldMusic n s p1 p2 t 
part)

I understand that when i use the foldMusic function i need to pass it 5 
parameters.  given the type signiature, why can i pass (+) as a parameter 
for p1 but not for n, what determines what can be passed as a parameter, 
because they all have the return type a??

I attempted to create a function that utilises the foldMusic function that 
counts the number of notes:

count_notes :: Music -> Integer
count_notes = foldMusic (\_-> \_ -> \_ -> 1) (\_ -> 0) (+) (+) (\_ -> \_ -> 
0)

it appears to work, i think. Yet i'm still not certain of how it does so.

This confuses me,
Is there anyway to represent other fold functions in a tree like 
representation as foldr (+) 0 would appear as such?
   +
  1 \
 +
2 \
   +
  3 \
 0

Regards,
confused Patrick
_
Hot chart ringtones and polyphonics. Go to  
http://ninemsn.com.au/mobilemania/default.asp

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another Newbie question :)

2003-11-05 Thread Derek Elkins
On Wed, 5 Nov 2003 07:17:23 -0800 (PST)
Hal Daume III <[EMAIL PROTECTED]> wrote:

> Keith is entirely correct.
> 
> > You can see this from the definition of foldr:
> > 
> > foldr :: (a -> b -> b) -> b -> [a] -> b
> > foldr f z   []   = z
> > foldr f z (x:xs) = f x (foldr f z xs)
> > 
> > where clearly every [] is replaced by z and every : by f.
> 
> I had heard this before when I was first beginning and didn't really
> find it "clear" :).  I think if you write foldr with f in infix
> notation it's a bit more clear:
> 
> > foldr f z   [] = z
> > foldr f z   (x:xs) = x `f` foldr f z xs
> 
> or even write the second line as
> 
> > foldr f z   (x:xs) = x `f` xs'
> >   where xs' = foldr f z xs
> 
> I think in this case it's a bit more clear how "f" is replacing the
> ":".
> 
>  - Hal

Simply choose better names,
data Tree a = Empty | Leaf a | Branch (Tree a) (Tree a)

foldTree empty leaf branch Empty = empty
foldTree empty leaf branch (Leaf a) = leaf a
foldTree empty leaf branch (Branch l r)
= branch (foldTree empty leaf branch l)
 (foldTree empty leaf branch r)

data List a = Nil | Cons a (List a)
foldList nil cons Nil = nil
foldList nil cons (Cons a as) = cons a (foldList nil cons as)

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another Newbie question :)

2003-11-05 Thread Hal Daume III
Keith is entirely correct.

> You can see this from the definition of foldr:
> 
> foldr :: (a -> b -> b) -> b -> [a] -> b
> foldr f z   []   = z
> foldr f z (x:xs) = f x (foldr f z xs)
> 
> where clearly every [] is replaced by z and every : by f.

I had heard this before when I was first beginning and didn't really find 
it "clear" :).  I think if you write foldr with f in infix notation it's a 
bit more clear:

> foldr f z   [] = z
> foldr f z   (x:xs) = x `f` foldr f z xs

or even write the second line as

> foldr f z   (x:xs) = x `f` xs'
>   where xs' = foldr f z xs

I think in this case it's a bit more clear how "f" is replacing the ":".

 - Hal


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Trying to understand tuples and lists

2003-11-05 Thread Hal Daume III
Based on this and your previous post, I think you're not understanding 
what "<-"/"do" are for.  I think you'll be better off forgetting them 
completely and using 'let/in' for now.

let (x,y) = head [...]
in  ...

is what you want.

On Wed, 5 Nov 2003, Karthik Kumar wrote:

> Hi, 
> I have a list of  tuples ( characters and numbers ) . 
> 
> say, [('a', 1), ('b', 2)]
> I want to extract 'a' and 1 separately . 
> 
> (x,y) <- head  [('a', 1), ('b', 2)]
> 
>   This doesnt work but my idea is to get x contain the value 'a' and y
> contain the value 1 as the first tuple in the list. 
>Which is the right way of doing this.  Thanks for your help. 
> 
> Cheers
> Karthik.
> 
> __
> Do you Yahoo!?
> Protect your identity with Yahoo! Mail AddressGuard
> http://antispam.yahoo.com/whatsnewfree
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another Newbie question :)

2003-11-05 Thread Keith Wansbrough
> Think of a list [1,2,3].  Recall this is "syntactic sugar" 
> (abbreviation) for 1:(2:(3:[])).  That looks like

FYI, I've just added my answer to your question to the Haskell Wiki, at

http://www.haskell.org/hawiki/WhatIsaFold

Enjoy!

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another Newbie question :)

2003-11-05 Thread Keith Wansbrough
> I seem to understand the basic idea behind the fold function, i think but do 
> not seem to be able to write them myself. My understanding is that it works 
> by replacing every constructor with a fold ?

I think you mean "replaces every constructor with a function or 
constant".

Think of a list [1,2,3].  Recall this is "syntactic sugar" 
(abbreviation) for 1:(2:(3:[])).  That looks like

:
   1 \
  :
 2 \
:
   3 \
 []

in memory.

Recall (+) is the function that takes two arguments and returns their
sum.

Now do

foldr (+) 0 [1,2,3]

What happens is that (:) is replaced by the first argument (+) and []
is replaced by the second argument 0, as follows:

+
   1 \
  +
 2 \
+
   3 \
  0

This is just 1+(2+(3+0)), which is 6.

You can see this from the definition of foldr:

foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f z   []   = z
foldr f z (x:xs) = f x (foldr f z xs)

where clearly every [] is replaced by z and every : by f.

A similar fold can be written for any datatype; it just takes a
different number of arguments, one for every constructor.  The general
term is "catamorphism".  E.g.:

data Expr = Num Int
  | Plus Expr Expr
  | Times Expr Expr

foldExpr :: Int -> (b -> b -> b) -> (b -> b -> b) -> b
foldExpr n p t (Num   i) = n i
foldExpr n p t (Plus  e1 e2) = p (foldExpr n p t e1) (foldExpr n p t e2)
foldExpr n p t (Times e1 e2) = t (foldExpr n p t e1) (foldExpr n p t e2)

Hope this helps.

> Could anyone please point me in the direction of a suitable resource of 
> attempt to explain this to me :)

You could try googling for "catamorphism", or looking at some of Erik
Meijer et al's papers on "bananas, lenses, and barbed wire" and so on.

--KW 8-)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Trying to understand tuples and lists

2003-11-05 Thread ketil+haskell
Karthik Kumar <[EMAIL PROTECTED]> writes:

> I got get this working thanks to the fst and snd function. 

>> (x,y) <- head  [('a', 1), ('b', 2)]

You could also (possibly easier to read) do it like the above, only
use an '='

(x,y) = head [('a', 1), ('b', 2)]

(The <- operator is used for monadic computations and list
comprehensions:

main = do
x <- readFile ...

or 

mapFst xs = [ x | (x,y) <- xs ]

) 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Trying to understand tuples and lists

2003-11-05 Thread Karthik Kumar
I got get this working thanks to the fst and snd function. 

Cheers
Karthik. 

--- Karthik Kumar <[EMAIL PROTECTED]> wrote:
> Hi, 
> I have a list of  tuples ( characters and numbers ) . 
> 
> say, [('a', 1), ('b', 2)]
> I want to extract 'a' and 1 separately . 
> 
> (x,y) <- head  [('a', 1), ('b', 2)]
> 
>   This doesnt work but my idea is to get x contain the value 'a' and
> y
> contain the value 1 as the first tuple in the list. 
>Which is the right way of doing this.  Thanks for your help. 
> 
> Cheers
> Karthik.
> 
> __
> Do you Yahoo!?
> Protect your identity with Yahoo! Mail AddressGuard
> http://antispam.yahoo.com/whatsnewfree
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe


__
Do you Yahoo!?
Protect your identity with Yahoo! Mail AddressGuard
http://antispam.yahoo.com/whatsnewfree
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Trying to understand tuples and lists

2003-11-05 Thread Karthik Kumar
Hi, 
I have a list of  tuples ( characters and numbers ) . 

say, [('a', 1), ('b', 2)]
I want to extract 'a' and 1 separately . 

(x,y) <- head  [('a', 1), ('b', 2)]

  This doesnt work but my idea is to get x contain the value 'a' and y
contain the value 1 as the first tuple in the list. 
   Which is the right way of doing this.  Thanks for your help. 

Cheers
Karthik.

__
Do you Yahoo!?
Protect your identity with Yahoo! Mail AddressGuard
http://antispam.yahoo.com/whatsnewfree
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-05 Thread Simon Peyton-Jones
| More overlapping:
| Allow any overlapping rules, and apply the most specific rule that
| matches our target. Only complain if there is a pair of matching
| rules neither of which is more specific than the other.
| This follow the spirit of the treatment of duplicate imports...

Happy days.  I've already implemented this change in the HEAD.  If you
can build from source, you can try it.

| Backtracking search:
| If several rules matched your target, and the one you picked didn't
| work, go back and try another.
| 
| This isn't as well through out: you probably want to backtrack through
all
| the matching rules even if some are unordered by being more specific.
It
| would probably be godd enough to respect specificity, and make other
| choices arbitrarilily (line number, filename, etc. maybe Prolog has a
| solution?). This probably isn't too hard if you can just add
| nondeterminism to the monad the code already lives in.

I didn't follow the details of this paragraph.  But it looks feasible.

| Overloading resolution:
| This one is really half-baked, but sometimes it would be nice if there
was
| some way to look at
| class MyNumber a where
|   one::a
| instance MyNumber Int where
|   one = 1
| 
| then see (one+1) and deduce that the 1 must have type Int, rather than
| complaining about being unable to deduce MyNumber a from Num a. This
is
| really nice for some cases, like a lifting class I wrote for an
Unlambda
| interpreter, with instances for LiftsToComb Comb and (LiftsToComb a =>
| LiftsToComb (a -> Comb)). With some closed world reasoning lift id and
| lift const might give you I and K rather than a type error. Also, for
| this work with modelling inheritance you almost always have to give
type
| signatures on numbers so you find the method that takes an Int, rather
| than not finding anything that takes any a with Num a. This obviously
| breaks down if you have instances for Int and Integer, and I don't yet
| know if it is worth the trouble for the benefits in the cases where it
| would help. Implementation is also a bit tricky. I think it requires
| unifying from both sides when deciding if a rule matches a goal.

I'm much less sure about this stuff.  Mark Shields and I did something
about closed classes in our OO paper
http://research.microsoft.com/~simonpj/Papers/oo-haskell/index.htm, and
Martin Sulzmann and colleagues have done lots of foundational work --
but the dust is still swirling I think.

Simon




___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Another Newbie question :)

2003-11-05 Thread Patty Fong
I seem to understand the basic idea behind the fold function, i think but do 
not seem to be able to write them myself. My understanding is that it works 
by replacing every constructor with a fold ?

Could anyone please point me in the direction of a suitable resource of 
attempt to explain this to me :)

Cheers,
Paty
_
Hot chart ringtones and polyphonics. Go to  
http://ninemsn.com.au/mobilemania/default.asp

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type errors in Haskell programming languages - Plz help

2003-11-05 Thread Karthik Kumar
Thanks Steffen. This one worked.  

Cheers
Karthik. 

--- [EMAIL PROTECTED] wrote:
> Hello.
>  
>  > The code is as follows - 
>  > <-- Code starts -->
>  > entry :: [Char] -> [(Char,Int)]
>  > entry list = do t <- getGroups list
>  > mergeGroups t
>  > 
>  > getGroups   :: [Char] -> [(Char,Int)]
>  > mergeGroups :: [(Char,Int)] -> [(Char,Int)]
>  > <-- Code Ends --> 
> 
>  You probably mean:
> 
>  entry list = let t = getGroups list in mergeGroups t
> 
>  or simpler
> 
>  entry = mergeGroups . getGroups
> 
>  Take a look at the instance Monad [ ] in the Prelude to
>  see, why your program does not work.
> 
>  Ciao,
>  Steffen
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe


__
Do you Yahoo!?
Protect your identity with Yahoo! Mail AddressGuard
http://antispam.yahoo.com/whatsnewfree
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type errors in Haskell programming languages - Plz help

2003-11-05 Thread s_mazanek
Hello.
 
 > The code is as follows - 
 > <-- Code starts -->
 > entry :: [Char] -> [(Char,Int)]
 > entry list = do t <- getGroups list
 > mergeGroups t
 > 
 > getGroups   :: [Char] -> [(Char,Int)]
 > mergeGroups :: [(Char,Int)] -> [(Char,Int)]
 > <-- Code Ends --> 

 You probably mean:

 entry list = let t = getGroups list in mergeGroups t

 or simpler

 entry = mergeGroups . getGroups

 Take a look at the instance Monad [ ] in the Prelude to
 see, why your program does not work.

 Ciao,
 Steffen

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Type errors in Haskell programming languages - Plz help

2003-11-05 Thread Karthik Kumar
Hi, 
  I was trying this Haskell program and was getting the following type
error. 

The code is as follows - 
<-- Code starts -->
entry :: [Char] -> [(Char,Int)]
entry list = do t <- getGroups list
mergeGroups t

getGroups   :: [Char] -> [(Char,Int)]
mergeGroups :: [(Char,Int)] -> [(Char,Int)]
<-- Code Ends --> 

  The function getGroups and mergeGroups compile perfectly fine. 

The error i am getting is in the function entry . To paste the message,


"
*** Expression : mergeGroups t
*** Term   : t
*** Type   : (Char,Int)
*** Does not match : [(Char,Int)]
"
 Thanks in advance for helping me in this regard.

Cheers
Karthik.

__
Do you Yahoo!?
Protect your identity with Yahoo! Mail AddressGuard
http://antispam.yahoo.com/whatsnewfree
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-05 Thread Ken Shan
Brandon Michael Moore <[EMAIL PROTECTED]> wrote in article <[EMAIL PROTECTED]> in 
gmane.comp.lang.haskell.cafe:
> There are two extensions here:
> 
> More overlapping: [...]
> Backtracking search: [...]
> 
> Overloading resolution: [...]

I'm sorry if I am getting ahead of Simon or behind of you, but have you
looked at

Simon L. Peyton Jones, Mark Jones, and Erik Meijer. 1997.  Type classes:
An exploration of the design space.  In Proceedings of the Haskell
workshop, ed. John Launchbury.
http://research.microsoft.com/Users/simonpj/papers/type-class-design-space/

?  There is quite a bit of design discussion there, and I am not sure
how much has been obsoleted by more recent advances.  A primary
consideration seems to be that the compiler should be guaranteed to
terminate (so type checking must be decidable).

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
hqrtzdfg
aooieoia
pnkplptr
ywwywyyw

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe