[Haskell-cafe] how would this be done? type classes? existential types?

2006-03-16 Thread Matthias Fischmann


hi,

this is one of those situations that always make scheme and perl
hackers laugh at me: i have written a piece of code that is
intuitively clear, and now i am trying to turn it into something that
compiles.  and here it goes.

i have a type class that looks something like this:

  class Resource a where
resourceName  :: a - String
resourceAdvance   :: a - a
resourceStarved   :: a - Bool
resourceSpend :: a - Int - a
resourceEarn  :: a - Int - a

resource types are rice, crude oil, pizza, software code, and so on.
they all have a different internal structure and the same abstract
interface, that's why i have defined this type class.

now i want to create a list of a type similar to

  [r1, r2, r3] :: (Resource a) = [a]

but with r1 being pizza, r2 being crude oil, and so on.  my first idea
was this:

  data Rs = forall a . (Resource a) = Rs a
  unRs (Rs a) = a
  rsName :: Rs - String
  rsName = resourceName . unRs
  ...

and then export Rs as an abstract data type.  this would allow for
lists of type [Rs], which is exactly what i want.

but what is the type of unRs?  or better: can i make it type at all?
and isn't this solution a little redundant and verbose?  should i do
it like in the example for existentially quantified types in the ghc
manual?

  http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html

but wouldnt't the code become really messy?  or should i do the type
class and instances, and then do Rs the existentially quantified way,
with all class methods arguments to the Rs constructor?  or is there a
completely different way to do this (besides using scheme or perl :-)?


thanks,
matthias


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] how would this be done? type classes? existentialtypes?

2006-03-16 Thread Geest, G. van den
Title: RE: [Haskell-cafe] how would this be done? type classes? existentialtypes?






Try using a GADT:

data Rs where
 Rs :: Resource a = a - Rs

class Resource a where
 resourceName :: a - String

instance Resource String where
 resourceName x = String

instance Resource Int where
 resourceName x = Int

resName (Rs x) = resourceName x

resNames = map resName

test = resNames [Rs Hi, Rs (1::Int) ]

The most important observations is that when pattern matching on (Rs x) we cannot make any assumptions about x, except using the class members of Resource.

We hope this will help you,

Gerrit (and the rest of the ST-lab)




-Original Message-
From: [EMAIL PROTECTED] on behalf of Matthias Fischmann
Sent: Thu 3/16/2006 12:57 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes?



hi,

this is one of those situations that always make scheme and perl
hackers laugh at me: i have written a piece of code that is
intuitively clear, and now i am trying to turn it into something that
compiles. and here it goes.

i have a type class that looks something like this:

 class Resource a where
 resourceName :: a - String
 resourceAdvance :: a - a
 resourceStarved :: a - Bool
 resourceSpend :: a - Int - a
 resourceEarn :: a - Int - a

resource types are rice, crude oil, pizza, software code, and so on.
they all have a different internal structure and the same abstract
interface, that's why i have defined this type class.

now i want to create a list of a type similar to

 [r1, r2, r3] :: (Resource a) = [a]

but with r1 being pizza, r2 being crude oil, and so on. my first idea
was this:

 data Rs = forall a . (Resource a) = Rs a
 unRs (Rs a) = a
 rsName :: Rs - String
 rsName = resourceName . unRs
 ...

and then export Rs as an abstract data type. this would allow for
lists of type [Rs], which is exactly what i want.

but what is the type of unRs? or better: can i make it type at all?
and isn't this solution a little redundant and verbose? should i do
it like in the example for existentially quantified types in the ghc
manual?

 http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html

but wouldnt't the code become really messy? or should i do the type
class and instances, and then do Rs the existentially quantified way,
with all class methods arguments to the Rs constructor? or is there a
completely different way to do this (besides using scheme or perl :-)?


thanks,
matthias




-Original Message-
From: [EMAIL PROTECTED] on behalf of Matthias Fischmann
Sent: Thu 3/16/2006 12:57 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes?



hi,

this is one of those situations that always make scheme and perl
hackers laugh at me: i have written a piece of code that is
intuitively clear, and now i am trying to turn it into something that
compiles. and here it goes.

i have a type class that looks something like this:

 class Resource a where
 resourceName :: a - String
 resourceAdvance :: a - a
 resourceStarved :: a - Bool
 resourceSpend :: a - Int - a
 resourceEarn :: a - Int - a

resource types are rice, crude oil, pizza, software code, and so on.
they all have a different internal structure and the same abstract
interface, that's why i have defined this type class.

now i want to create a list of a type similar to

 [r1, r2, r3] :: (Resource a) = [a]

but with r1 being pizza, r2 being crude oil, and so on. my first idea
was this:

 data Rs = forall a . (Resource a) = Rs a
 unRs (Rs a) = a
 rsName :: Rs - String
 rsName = resourceName . unRs
 ...

and then export Rs as an abstract data type. this would allow for
lists of type [Rs], which is exactly what i want.

but what is the type of unRs? or better: can i make it type at all?
and isn't this solution a little redundant and verbose? should i do
it like in the example for existentially quantified types in the ghc
manual?

 http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html

but wouldnt't the code become really messy? or should i do the type
class and instances, and then do Rs the existentially quantified way,
with all class methods arguments to the Rs constructor? or is there a
completely different way to do this (besides using scheme or perl :-)?


thanks,
matthias





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


[Haskell-cafe] how would this be done? type classes? existentialtypes?

2006-03-16 Thread Matthias Fischmann

yes, that helps.  also thanks to lennart and chris, i think i got it
working.

...  and have more questions: is there any difference between these
two?  if they are equivalent, why the two different ways to say it?

  data X where X :: (Resource a) = a - X
  data Y = forall a . (Resource a) = Y a

and now it gets interesting: i need instances for Rs on Show, Read,
Eq, Ord.  Show is very simple, but Read?  if i look at a string, it's
already to late to decide which type is has, right?  same problem with
Eq: i could first check whether the rsNames match and if so, go ahead
and compare the two resource class instances inside Rs.  but the type
system would never know whether this is safe or not.

solution: add methods rsEq, rsOrd to the Resource class and use them
to instantiate Eq, and Ord respectively.  this is not pretty, but not
particularly ugly either, and it works.

but this still doesn't work for Read, right?

m.



On Thu, Mar 16, 2006 at 01:37:36PM +0100, Geest, G. van den wrote:
 To: Matthias Fischmann [EMAIL PROTECTED], haskell-cafe@haskell.org
 From: Geest, G. van den [EMAIL PROTECTED]
 Date: Thu, 16 Mar 2006 13:37:36 +0100
 Subject: RE: [Haskell-cafe] how would this be done? type classes? 
 existentialtypes?
 
 Try using a GADT:
 
 data Rs where
   Rs :: Resource a = a - Rs
 
 class Resource a where
 resourceName  :: a - String
 
 instance Resource String where
 resourceName x = String
 
 instance Resource Int where
 resourceName x = Int
 
 resName (Rs x) = resourceName x
 
 resNames = map resName
 
 test = resNames [Rs Hi, Rs (1::Int) ]
 
 The most important observations is that when pattern matching on (Rs x) we 
 cannot make any assumptions about x, except using the class members of 
 Resource.
 
 We hope this will help you,
 
 Gerrit (and the rest of the ST-lab)
 
 
 
 
 -Original Message-
 From: [EMAIL PROTECTED] on behalf of Matthias Fischmann
 Sent: Thu 3/16/2006 12:57 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] how would this be done? type classes? 
 existentialtypes?
  
 
 
 hi,
 
 this is one of those situations that always make scheme and perl
 hackers laugh at me: i have written a piece of code that is
 intuitively clear, and now i am trying to turn it into something that
 compiles.  and here it goes.
 
 i have a type class that looks something like this:
 
   class Resource a where
 resourceName  :: a - String
 resourceAdvance   :: a - a
 resourceStarved   :: a - Bool
 resourceSpend :: a - Int - a
 resourceEarn  :: a - Int - a
 
 resource types are rice, crude oil, pizza, software code, and so on.
 they all have a different internal structure and the same abstract
 interface, that's why i have defined this type class.
 
 now i want to create a list of a type similar to
 
   [r1, r2, r3] :: (Resource a) = [a]
 
 but with r1 being pizza, r2 being crude oil, and so on.  my first idea
 was this:
 
   data Rs = forall a . (Resource a) = Rs a
   unRs (Rs a) = a
   rsName :: Rs - String
   rsName = resourceName . unRs
   ...
 
 and then export Rs as an abstract data type.  this would allow for
 lists of type [Rs], which is exactly what i want.
 
 but what is the type of unRs?  or better: can i make it type at all?
 and isn't this solution a little redundant and verbose?  should i do
 it like in the example for existentially quantified types in the ghc
 manual?
 
   http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html
 
 but wouldnt't the code become really messy?  or should i do the type
 class and instances, and then do Rs the existentially quantified way,
 with all class methods arguments to the Rs constructor?  or is there a
 completely different way to do this (besides using scheme or perl :-)?
 
 
 thanks,
 matthias
 
 
 
 
 -Original Message-
 From: [EMAIL PROTECTED] on behalf of Matthias Fischmann
 Sent: Thu 3/16/2006 12:57 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] how would this be done? type classes? 
 existentialtypes?
  
 
 
 hi,
 
 this is one of those situations that always make scheme and perl
 hackers laugh at me: i have written a piece of code that is
 intuitively clear, and now i am trying to turn it into something that
 compiles.  and here it goes.
 
 i have a type class that looks something like this:
 
   class Resource a where
 resourceName  :: a - String
 resourceAdvance   :: a - a
 resourceStarved   :: a - Bool
 resourceSpend :: a - Int - a
 resourceEarn  :: a - Int - a
 
 resource types are rice, crude oil, pizza, software code, and so on.
 they all have a different internal structure and the same abstract
 interface, that's why i have defined this type class.
 
 now i want to create a list of a type similar to
 
   [r1, r2, r3] :: (Resource a) = [a]
 
 but with r1 being pizza, r2 being crude oil, and so on.  my first idea
 was this:
 
   data Rs = forall a . (Resource a) = Rs a
   unRs (Rs a) = a
   rsName :: Rs

Re: [Haskell-cafe] how would this be done? type classes? existential types?

2006-03-16 Thread Matthias Fischmann

On Thu, Mar 16, 2006 at 12:40:00PM +, Chris Kuklewicz wrote:
 (Why isn't it resourceName :: String ?)

because i am too clumsy.  (-:

when i am trying this, ghc complains that the type of resourceName
doesn't have any occurrance of 'a', and i feel that it must be harder
for the type engine to figure things out if there isn't, so
resourceName is still a mapping from resources to their names.

did i miss anything?


m.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how would this be done? type classes? existential types?

2006-03-16 Thread Matthias Fischmann

Alexandra Silva [EMAIL PROTECTED] wrote:
 http://homepages.cwi.nl/~ralf/HList/

this looks like it might address my problems with Read / Eq
instantiation?  will read.

thanks again to everybody.



m.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: alternative translation of type classes to CHR(was:relaxedinstance rules spec)

2006-03-13 Thread Claus Reinke

[still talking to myself..?]

all confluence problems in the FD-CHR paper, as far as they were 
not due to instances inconsistent with the FDs, seem to be due to 
conflicts between improvement and inference rules. we restore 
confluence by splitting these two constraint roles, letting inference 
and improvements work on constraints in separate roles, thus 
removing the conflicts.


I should have mentioned that the improved confluence obtained by
separating the dimensions of FD-based improvement and instance
inference buys us a lot more than just permitting more valid programs
(compared to the original, incomplete CHR):

- separating the two dimensions of inference and improvement leads
   to better confluence (implementations are no longer forced to
   iterate improvement before continuing inference; fewer conservative
   restrictions are needed in the static semantics of TC; more valid
   code can be accepted)

- better confluence guarantees that all improvement rules that apply will 
   be run eventually, which means that the new CHR is self-checking 
   wrt FD consistency! 

   [if consistency is violated, there are at least two instances with 
   different FD range types for the same FD domain types; that 
   means there will be two instance improvement rules with the 
   same lhs, but different equations on their rhs; if any constraint 
   arises that would run into the FD inconsistency by using one 
   of those improvement rules, the other will cause the derivation 
   to fail]


we can see this in action by looking at the relevant example of the
FD-CHR paper (last revised Feb2006), section 5.1 Confluence,
example 5:

   class Mul a b c | a b - c
   instance Mul Int Float Float
   instance Mul Int Float Int

the old CHR for this example (which violates FD consistency) is 
not confluent, allowing derivation of both c=Float and c=Int for

the constraint Mul Int Float c. the revised paper still claims that
consistency is inuitively necessary to guarantee confluence (it
also still claims that it isn't sufficient, referring to the example we
dealt with in the previous email).

but if we apply the new Tc2CHR translation, we obtain a
confluent CHR for the same example (there doesn't appear
to be a way to switch off the consistency check in GHC, so
I had to translate the two instances separately..):

   mul(A,B,C) = infer_mul(A,B,C), memo_mul(A,B,C).

   /* functional dependencies */
   memo_mul(A,B,C1), memo_mul(A,B,C2) == C1=C2.

   /* instance inference: */
   infer_mul(int,float,float) = true.
   infer_mul(int,float,int) = true.

   /* instance improvements: */
   memo_mul(int,float,C) == C=float.
   memo_mul(int,float,C) == C=int.

now, if we consider the problematic constraint again, and its two
initially diverging derivations, we see that the derivations can be
rejoined, exposing the inconsistency:

   mul(int,float,C)
= infer_mul(int,float,C), memo_mul(int,float,C)
[
== infer_mul(int,float,C), memo_mul(int,float,C), C=float
= true, memo_mul(int,float,float), C=float
== memo_mul(int,float,float), C=float, float=int
|
== infer_mul(int,float,C), memo_mul(int,float,C), C=int
= true, memo_mul(int,float,int), C=int
== memo_mul(int,float,int), C=int, int=float
] 
= fail
  
this dynamic safety does not mean that we should drop the 
consistency check in the static semantics completely! but whereas
the old CHR translation _depends_ on the consistency check for 
safety, and is therefore stuck with it, the new translation gives us 
some manouvering space when we try to relax that check to 
account for the combination of overlap resolution and FDs.


cheers,
claus

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: alternative translation of type classes to CHR(was:relaxedinstance rules spec)

2006-03-13 Thread Taral
On 3/13/06, Claus Reinke [EMAIL PROTECTED] wrote:
 [still talking to myself..?]

This is all wonderful stuff! Are you perhaps planning to put it all
together into a paper?

What effect do you think this can have on existing algorithms to resolve FDs?

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: alternative translation of type classes to CHR(was:relaxedinstance rules spec)

2006-03-13 Thread Claus Reinke

Thanks, Taral,

it is good to know that I'm not just writing for the archives!-)

a paper, yes, at some point (unless someone shoots a hole in my
suggestions first;), but at the moment, I'm more concerned with
keeping my hopes for Haskell' alive, and completing my case. 

when Haskell' was announced, most of us thought that the committee 
would just collect all those old and proven extensions like MPTC, 
FDs, overlapping instances, undecidable instances, more flexible 
instances, etc., figure out the common story behind them and weave 
all of that into a coherent new standard, leaving the newer extensions 
like GADTs, ATS, etc. for future standards. unfortunately, the idea 
that well-established popular extensions implied well-defined 
behaviour turned out to be an illusion, so unless we're doing the 
work now, we're not going to have the useful standard we wanted.


which makes it all the more important to have genuine discussions
here - there are so many extensions that have been proposed and
partially implemented over the years since Haskell 98, for which 
noone is even bothering to speak up on this list (generics in their
various forms and implementations? better support for faking 
dependent types? template meta-programming? a genuine type 
Dynamic, as in Clean? ..). I am a bit worried that many 
Haskellers appear to have given up listening here, let alone 
arguing for their interests. and with the extreme timeline the 
committee is insisting on, there just wont be time to wait for

the first draft and start complaining then.

I can't argue for all the features I'm missing in the discussions so
far, but I can try to help with a few of them, and hope that others
will wake up before the committee closes the doors.

you ask about effects on existing handling of FDs: I appreciate the 
work that has gone into FD-CHR, and into the refined conditions 
now implemented in GHC head, but I cannot accept them as the 
last word (for reasons explained in previous emails, the restrictions 
are too restrictive in practice, for real programs; eg. since the 
change, I suddenly have to use undecidable instances for 
instances that are obviously decidable, which kind of defeats the

purpose of that flag; as a minimum benchmark, I'd like to be
able to use the Data.Record.hs stuff, in its simple form, without
the hacks, in whatever Haskell' turns out to be - and currently,
we are far from passing that criterium). 

I hope I have now explained what I meant when I said that most 
of the confluence issues were due to the translation, not inherent 
in FDs, and I intend to use this groundwork for tackling the 
combination of FDs and overlap resolution, in the way explained 
informally in my early emails here. I also hope that this simpler 
basis might help implementors to simplify and gain more confidence

in their code bases (in which these features have grown over years,
in wild combinations with other experiments, often driven only by 
examples and counter-examples).


unfortunately, tracking down the reasons for why these conditions 
were considered necessary in this form has been a slow process, 
as has been trying to show that they might not be. so it really helps 
to know that I'm not the only one who expects more from Haskell'.


having the formal specification in the FD-CHR paper, and having 
some of it implemented in GHC, is one of the best examples of the 
Haskell' process actually producing useful deliverables, and could
set the example for the other aspects of Haskell'. so I can only 
encourage Haskellers to read the paper, and to try GHC head,

and see whether they can live with the suggested limitations and
formalizations. if not, raise your voice here, now!

cheers,
claus

- Original Message - 
From: Taral [EMAIL PROTECTED]

To: Claus Reinke [EMAIL PROTECTED]
Cc: haskell-prime@haskell.org
Sent: Monday, March 13, 2006 10:57 PM
Subject: Re: alternative translation of type classes to CHR(was:relaxedinstance 
rules spec)


On 3/13/06, Claus Reinke [EMAIL PROTECTED] wrote:

[still talking to myself..?]


This is all wonderful stuff! Are you perhaps planning to put it all
together into a paper?

What effect do you think this can have on existing algorithms to resolve FDs?

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
   -- Edsger Dijkstra
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: alternative translation of type classes to CHR (was:relaxedinstance rules spec)

2006-03-08 Thread Claus Reinke
a second oversight, in variation B: CHR rules are selected by matching, 
not by unification (which is quite essential to modelling the way type 
class inference works). this means that the idea of generating memo_

constraints for the instance fdis and relying on the clas fdi rules to
use that information is not going to work directly. 


however, we can look at the intended composition of those fdi instance
rules with the fdi class rules, and specialize the latter when applied to 
the rhs of the former (assuming unification while doing so).


!!
the nice thing about this is that variation B now looks very much like
the original translation, differing only in the splitting of roles, without
any other tricks merged in. that means it should now be more obvious
why variation B is a modification of the original translation with better
confluence properties. 

all confluence problems in the FD-CHR paper, as far as they were 
not due to instances inconsistent with the FDs, seem to be due to 
conflicts between improvement and inference rules. we restore 
confluence by splitting these two constraint roles, letting inference 
and improvements work on constraints in separate roles, thus 
removing the conflicts.


= Tc2CHR alternative, with separated roles

   class C = TC a1..an | fd1,..,fdm

   where fdi is of the form: ai1..aik - ai0

   -  TC a b = infer_TC a b, memo_TC a b, C. (two roles +superclasses)

   -  memo_TC  a1..an, memo_TC th(b1)..th(bn) = ai0=bi0. (fdi)

where th(bij) | j0 = aij
  th(bl)  | not (exists j0. l==ij) = bl 


= Variation B (separate instance inference/FD improvement):

   instance C = TC t1..tn

   - infer_TC t1..tn = C.   (instance inference)

   - memo_TC th(b1)..th(bn) = ti0=bi0. (fdi instance improvement)

where th(bij) | j0 = tij
  th(bl)  | not (exists j0. l==ij) = bl 


=

in particular, the new CHRs for examples 14 and 18 (coverage violations,
hence not variable-restricted, hence confluence proof doesn't apply)
should now be confluent, because even after simplification, we can still use 
the class FDs for improvement.


here are the relevant rules for example 14:

   /* one constraint, two roles + superclasses */
   eval(Env,Exp,T) = infer_eval(Env,Exp,T), memo_eval(Env,Exp,T), true.

   /* functional dependencies */
   memo_eval(Env,Exp,T1), memo_eval(Env,Exp,T2) == T1=T2.

   /* instance inference: */
   infer_eval(Env,expAbs(X, Exp),to(V1, V2)) = eval(cons((X, V1), Env), Exp, 
V2).

   /* instance improvements: */
   memo_eval(Env_,Exp_,T_) == T_=to(V1, V2).

and the troublesome example constraints:

   eval(Env,expAbs(X,Exp),T1), eval(Env,expAbs(X,Exp),T2).
-
   infer_eval(Env,expAbs(X,Exp),T1), infer_eval(Env,expAbs(X,Exp),T2), 
   memo_eval(Env,expAbs(X,Exp),T1), memo_eval(Env,expAbs(X,Exp),T2).


[
- [class FD first]
   infer_eval(Env,expAbs(X,Exp),T2), memo_eval(Env,expAbs(X,Exp),T2),
   T1=T2.
|
- [instance improvement and simplification first]
   eval(cons((X,V11),Env),Exp,V12), eval(cons((X,V21),Env),Exp,V22), 
   memo_eval(Env,expAbs(X,Exp),T1), memo_eval(Env,expAbs(X,Exp),T2),

   T1=to(V11,V12), T2=to(V21,V22).
]

- [rejoin inferences]
   eval(cons((X,V21),Env),Exp,V22), 
   memo_eval(Env,expAbs(X,Exp),T2),

   T1=T2, T2=to(V21,V22).
- ..

cheers,
claus

ps I've only listed the updated variation B here, to limit confusion. if you 
   want the updated code and full text, you should be able to use


   darcs get http://www.cs.kent.ac.uk/~cr3/chr/

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


[Haskell-cafe] type inference algorithm for type classes

2005-11-30 Thread robert wong

Hi All,

I have been developing a type inference system which is very similar to type 
classes' (by Wadler and Blott). However, I cannot find a detailed 
description of the algorithm. In Type Classes in Haskell, implementation 
issues are discussed briefly. However, it is too brief for me to grasp. Does 
anybody have any suggestion on where to look?


Thanks,
Robert

_
Get an advanced look at the new version of MSN Messenger. 
http://messenger.msn.com.sg/Beta/Default.aspx


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


Re: [Haskell-cafe] type inference algorithm for type classes

2005-11-30 Thread Ronny Wichers Schreur
robert wong writes (in the Haskell Cafe):

 I have been developing a type inference system which is very similar to
 type classes' (by Wadler and Blott). However, I cannot find a detailed
 description of the algorithm. In Type Classes in Haskell,
 implementation issues are discussed briefly. However, it is too brief
 for me to grasp. Does anybody have any suggestion on where to look?

See Mark Jones's Typing Haskell in Haskell
http://www.cse.ogi.edu/~mpj/thih/.


Cheers,

Ronny Wichers Schreur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes and hFoldr from HList

2005-11-07 Thread Greg Buchholz
Ralf Lammel wrote:
 
 What you can do is define a dedicated *type code* for composition.
 
 comp  = hFoldr (undefined::Comp) (id::Int - Int) test
 
 data Comp
 
 instance Apply Comp (x - y,y - z) (x - z)
  where
   apply _ (f,g) = g . f

That does it!


Thanks,

Greg Buchholz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Families of type classes

2005-11-06 Thread Fraser Wilson
On 11/6/05, Klaus Ostermann [EMAIL PROTECTED] wrote:
instance Node Person where isConnectedTo g n (p1,p2) = (p1 == n) || (p2 == n)

At this point, isConnectedTo knows nothing about the third argument
except that it is an edge, and there's no reason to think that an Edge
is a tuple. All you can say is that there are two functions, n1
and n2, which extract the nodes of the edge. Use those instead,
for example

isConnectedTo g n p = n == n1 p || n == n2 p

 Couldn't match the rigid variable `e' against `(a, b)'`e' is bound by the type signature for `isConnectedTo'
Expected type: eInferred type: (a, b)When checking the pattern: (p1, p2)In the definition of `isConnectedTo':isConnectedTo g n (p1, p2) = (p1 == n) || (p2 == n)
Hopefully this error makes more sense now. It's saying that it expected something of type 'e', but it found a tuple.

regards,
Fraser.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Families of type classes

2005-11-06 Thread Daniel Fischer
Hi Klaus,
I think, for graphs at least, you should use a different approach.
The function isConnectedTo only makes sense in the context of a graph,
so class Node -- as it stands -- has no reason to be. Further, in your 
approach, you have the problem that instances of Edge are hard
to define, because the Node-type can't be inferred (nothing prevents an
instance Graph g' Int Likes, say with n1 g (p1,_) = length p1), so this won't 
compile, you must provide further information about the Node-type in the 
Edge class. It's fixable:

class (Node n, Edge e n) = Graph g n e | g - n, g - e where

class Node n where
   isConnectedTo :: Graph g n e = g - n - e - Bool

class Edge e n | e - n where
  n1 :: Graph g n e  = g - e - n
  n2 :: Graph g n e  = g - e - n

type Person = String
type Likes = (Person, Person)

data DummyGraph = DummyGraph String

instance Graph DummyGraph Person Likes where

instance Node Person where
   isConnectedTo g n e = n1 g e == n || n2 g e == n

instance Edge Likes Person where
   n1 g (p1,p2) = p1
   n2 g (p1,p2) = p2

But I don't like it.

I'd prefer (very strongly) something like

class Graph g n e | g - n, g - e where
isConnectedTo :: g - n - e - Bool  -- or perhaps rather without g
startNode, endNode :: e - n
. . . -- other Methods of interest like nodes, edges, components . . .

with, e.g.

instance Graph (Map node [node]) node (node,node) where . . .


Cheers, Daniel


Am Sonntag, 6. November 2005 15:01 schrieb Klaus Ostermann:
 Hi all,

 I am not a Haskell expert, and I am currently exploring type classes and
 need some advice.

 I want to define a family of mutually recursive types
 as a collection of type classes and then I want to be able
 to map these collections of types to a set of other types
 using instance declarations.

 For example, I have a type family for graphs, consisting of
 the types Node and Edge. In another part of my application
 I have the types Person and Likes (a pair of persons), and
 I want to map the roles Node and Edge to Person and Likes,
 respectively.

 It seems to me that functional dependencies could be a way to
 model it (maybe it can also be done much simpler, but I don't know how).

 Here is what I tried:

 class (Node n, Edge e) = Graph g n e | g - n, g - e where

 class Node n where
isConnectedTo :: Graph g n e = g - n - e - Bool

 class Edge e where
   n1 :: Graph g n e  = g - e - n
   n2 :: Graph g n e  = g - e - n

 type Person = String
 type Likes = (Person, Person)

 data DummyGraph = DummyGraph String

 instance Graph DummyGraph Person Likes where

 instance Node Person where
isConnectedTo g n (p1,p2) = (p1 == n) || (p2 == n)

 instance Edge Likes where
n1 g (p1,p2) = p1
n2 g (p1,p2) = p2

 This DummyGraph thing is supposed to be used as a kind of family object
 which stands for a particular type class family. However, this is not yet
 quite right because I get the error message

   Couldn't match the rigid variable `e' against `(a, b)'
 `e' is bound by the type signature for `isConnectedTo'
 Expected type: e
 Inferred type: (a, b)
   When checking the pattern: (p1, p2)
   In the definition of `isConnectedTo':
   isConnectedTo g n (p1, p2) = (p1 == n) || (p2 == n)

 Similar error messages occur in the instance declaration for Edge/Likes.

 I don't understand exactly what my error is. Maybe I would need a
 completely different strategy to model this.

 Any help would be appreciated!

 Regards,
 Klaus
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Families of type classes

2005-11-06 Thread Klaus Ostermann

Daniel Fischer schrieb:

I'd prefer (very strongly) something like

class Graph g n e | g - n, g - e where
isConnectedTo :: g - n - e - Bool  -- or perhaps rather without g
startNode, endNode :: e - n
. . . -- other Methods of interest like nodes, edges, components . . .

with, e.g.

instance Graph (Map node [node]) node (node,node) where . . .


Thanks for the suggestion. This looks good, but
it seems as if the g needs to occur in every signature, otherwise
the interpreter throws a No instance for ... arising from ...
error if you want to apply the function. Hence startNode would need to be
startNode :: g - e - n rather than startNode :: e - n

Is there any way to get rid of this dummy argument?

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


Re: [Haskell-cafe] Families of type classes

2005-11-06 Thread Daniel Fischer
Am Sonntag, 6. November 2005 17:30 schrieb Klaus Ostermann:
 Daniel Fischer schrieb:
  I'd prefer (very strongly) something like
 
  class Graph g n e | g - n, g - e where
  isConnectedTo :: g - n - e - Bool  -- or perhaps rather without
  g startNode, endNode :: e - n
  . . . -- other Methods of interest like nodes, edges, components
  . . .
 
  with, e.g.
 
  instance Graph (Map node [node]) node (node,node) where . . .

 Thanks for the suggestion. This looks good, but
 it seems as if the g needs to occur in every signature, otherwise
 the interpreter throws a No instance for ... arising from ...
 error if you want to apply the function. Hence startNode would need to be
 startNode :: g - e - n rather than startNode :: e - n

 Is there any way to get rid of this dummy argument?

 Klaus

Two I see, 
1. retain class Edge,

class Edge e n | e - n, n - e where
isConnectedTo :: n - e - Bool
startNode, endNode :: e - n

and then

class (Edge e n) = Graph g n e | g - n, g - e where
 -- other methods if wanted

2. add more FunDeps,

class Graph g n e | g - n, g - e, e - n, n - e, n e - g where . . . 

works.

Probably the second isn't wanted, because it introduces too much rigidity and 
an ADT might be better.

Cheers,
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Families of type classes

2005-11-06 Thread Udo Stenzel
Klaus Ostermann wrote:
 I am not a Haskell expert, and I am currently exploring type classes
 and need some advice.

The most important advice is probably to point out that a `class' in
Haskell is roughly comparable to an `interface' in Java, but not to a
`class'.

 class Node n where
   isConnectedTo :: Graph g n e = g - n - e - Bool

This is not what you want.  The type says: Every node can find out
whether it is connected to a given edge _in_any_type_of_graph_, which
is clearly impossible given that your Graph class has no methods.

Is your setting the notion of being a `Node' only makes sense in
connection with a type of `Graph'.  The right thing to so is probably to
drop the classes `Edge' and `Node' and put their methods into the
`Graph' class.

class Graph g n e | g - n e where
isConnectedTo :: g - n - e - Bool
n1 :: g - e - n
n2 :: g - e - n


Udo.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes and hFoldr from HList

2005-11-06 Thread Greg Buchholz

  I was playing around with the HList library from the paper...

Strongly typed heterogeneous collections
http://homepages.cwi.nl/~ralf/HList/

...and I thought I'd try to fold the composition function (.) through a
heterogeneous list of functions, using hFoldr...

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

import CommonMain

main = print $ comp abc

test = HCons ((+1)::(Int-Int)) (HCons ((*2)::(Int-Int)) (HCons length HNil))

comp = hFoldr (.) id test

instance Apply (a - b - c - d) (a, b) (c - d)  
where
apply f (a,b) = f a b

...but it fails with the following type error...

]Compiling Main ( compose.hs, interpreted )
]
]compose.hs:10:7:
]No instances for (Apply ((b - c) - (a - b) - a - c)
](Int - Int, r)
]([Char] - a3),
]  Apply ((b - c) - (a - b) - a - c) (Int - Int, r1) 
r,
]  Apply ((b - c) - (a - b) - a - c) ([a2] - Int, a1 
-a1) r1)
]  arising from use of `hFoldr' at compose.hs:10:7-12
]Probable fix:
]  add an instance declaration for (Apply ((b - c) - (a - b) - a - c)
] (Int - Int, r)
] ([Char] - a3),
]   Apply ((b - c) - (a - b) - a - c)
](Int - Int, r1) r,
]   Apply ((b - c) - (a - b) - a - c)
]([a2] - Int, a1 - a1) r1)
]In the definition of `comp': comp = hFoldr (.) id test

...Anyway, I couldn't quite tell whether I was using hFoldr incorrectly,
or if I needed to have more constraints placed on the construction of
test, or if needed some sort of type-level function that resolves...

Apply ((b - c) - (a - b) - a - c)

...into (a - c), or something else altogether.  I figured someone might
be able to help point me in the right direction.


Thanks,

Greg Buchholz

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


RE: [Haskell-cafe] Type classes and hFoldr from HList

2005-11-06 Thread Ralf Lammel
Hi Greg,

Since hfoldr is right-associative, I prefer to reorder your list of
functions as follows:

 test = HCons (length::String - Int) (HCons ((+1)::(Int-Int)) (HCons
((*2)::(Int-Int)) HNil))

Note that I also annotated length with its specific type.
(If you really wanted to leave things more polymorphic, you would need
to engage in TypeCast.)

Providing a specific Apply instance for (.) is not necessary, strictly
necessary. We could try to exploit the normal function instance for
Apply.

Let me recall that one here for convenience:

instance Apply (x - y) x y
 where
  apply f x = f x

Let me also recall the hFoldr instances:

class HList l = HFoldr f v l r | f v l - r
 where
  hFoldr :: f - v - l - r

instance HFoldr f v HNil v
 where
  hFoldr _ v _ = v

instance ( HFoldr f v l r
 , Apply f (e,r) r'
 )
  = HFoldr f v (HCons e l) r'
 where
  hFoldr f v (HCons e l) = apply f (e,hFoldr f v l)


To fit in (.), we would flip and uncurry it.
So we could try:

comp' = hFoldr (uncurry (flip (.))) (id::Int - Int) test

This wouldn't work.
The trouble is the required polymorphism of the first argument of
hFoldr.
The type of that argument as such is polymorphic.
However, this polymorphism does not survive type class parameterization.
You see this by looking at the HCons instance of HFoldr.
The different occurrences of f would need to be used at different
types.
This would only work if the type class parameter f were instantiated by
the polymorphic type of (uncurry (flip (.))). (And even then we may need
something like TypeCast.)

What you can do is define a dedicated *type code* for composition.

comp  = hFoldr (undefined::Comp) (id::Int - Int) test

data Comp

instance Apply Comp (x - y,y - z) (x - z)
 where
  apply _ (f,g) = g . f


Ralf


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Greg Buchholz
 Sent: Sunday, November 06, 2005 7:01 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Type classes and hFoldr from HList
 
 
   I was playing around with the HList library from the paper...
 
 Strongly typed heterogeneous collections
 http://homepages.cwi.nl/~ralf/HList/
 
 ...and I thought I'd try to fold the composition function (.) through
a
 heterogeneous list of functions, using hFoldr...
 
 {-# OPTIONS -fglasgow-exts #-}
 {-# OPTIONS -fallow-undecidable-instances #-}
 
 import CommonMain
 
 main = print $ comp abc
 
 test = HCons ((+1)::(Int-Int)) (HCons ((*2)::(Int-Int)) (HCons
length
 HNil))
 
 comp = hFoldr (.) id test
 
 instance Apply (a - b - c - d) (a, b) (c - d)
 where
 apply f (a,b) = f a b
 
 ...but it fails with the following type error...
 
 ]Compiling Main ( compose.hs, interpreted )
 ]
 ]compose.hs:10:7:
 ]No instances for (Apply ((b - c) - (a - b) - a - c)
 ](Int - Int, r)
 ]([Char] - a3),
 ]  Apply ((b - c) - (a - b) - a - c) (Int -
Int,
 r1) r,
 ]  Apply ((b - c) - (a - b) - a - c) ([a2] -
 Int, a1 -a1) r1)
 ]  arising from use of `hFoldr' at compose.hs:10:7-12
 ]Probable fix:
 ]  add an instance declaration for (Apply ((b - c) - (a - b) -
a -
  c)
 ] (Int - Int, r)
 ] ([Char] - a3),
 ]   Apply ((b - c) - (a - b) -
a -
  c)
 ](Int - Int, r1) r,
 ]   Apply ((b - c) - (a - b) -
a -
  c)
 ]([a2] - Int, a1 - a1) r1)
 ]In the definition of `comp': comp = hFoldr (.) id test
 
 ...Anyway, I couldn't quite tell whether I was using hFoldr
incorrectly,
 or if I needed to have more constraints placed on the construction of
 test, or if needed some sort of type-level function that resolves...
 
 Apply ((b - c) - (a - b) - a - c)
 
 ...into (a - c), or something else altogether.  I figured someone
might
 be able to help point me in the right direction.

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


[Haskell-cafe] Re: Using type classes for polymorphism of data constructors

2005-06-23 Thread Thomas Sutton

On 11/06/2005, at 11:18 PM, Thomas Sutton wrote:
In Java (C#, Python, etc) I'd do this by writing an interface  
Formula and have a bunch of abstract classes (PropositionalFormula,  
ModalFormula, PredicateFormula, etc) implement this interface, then  
extend them into the connective classes Conjunction, Disjunction,  
etc. The constructors for these connective classes would take a  
number of Formula values (as appropriate for their arity).


I've tried to implement this sort of polymorphism in Haskell using  
a type class, but I have not been able to get it to work and have  
begun to work on implementing this composition of logics in the  
DSL compiler, rather than the generated Haskell code. As solutions  
go, this is far from optimal.


Can anyone set me on the right path to getting this type of  
polymorphism working in Haskell? Ought I be looking at dependant  
types?


I've finally managed to find a way to get this to work using  
existentially quantified type variables and am posting it here for  
the benefit of the archives (and those novices like myself who will  
look to them in the future). My solution looks something like the  
following:


A type class over which the constructors ought to be polymorphic:

 class (Show f) = Formula f where
 language :: f - String

A type exhibiting such polymorphism:

 data PC
 = Prop String
 | forall a.   (Formula a)= Neg a
 | forall a b. (Formula a, Formula b) = Conj a b
 | forall a b. (Formula a, Formula b) = Disj a b
 | forall a b. (Formula a, Formula b) = Impl a b
 instance Formula PC where
 language _ = Propositional Calculus
 instance Show PC where
 show (Prop s)   = s
 show (Neg s)= ~ ++ (show s)
 show (Conj a b) = (show a) ++  /\\  ++ (show b)
 show (Disj a b) = (show a) ++  \\/  ++ (show b)
 show (Impl a b) = (show a) ++  -  ++ (show b)

Another such type:

 data Modal
 = forall a. (Formula a) = Poss a
 | forall b. (Formula b) = Necc b
 instance Formula Modal where
 language _ = Modal Logic
 instance Show Modal where
 show (Poss a) =  ++ (show a)
 show (Necc a) = [] ++ (show a)

Some example values of those types:

Main :t (Prop p)-- p
Prop p :: PC

Main :t (Poss (Prop p))-- p
Poss (Prop p) :: Modal

Main :t (Impl (Prop p) (Poss (Prop p)))-- p - p
Impl (Prop p) (Poss (Prop p)) :: PC

I also have a sneaking suspicion I'd also be able to solve this  
problem using dependant types, but I have not investigated that  
approach.


Cheers,
Thomas Sutton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Using type classes for polymorphism of dataconstructors

2005-06-23 Thread Ralf Lammel
Thomas Sutton wrote:

 Main :t (Impl (Prop p) (Poss (Prop p)))-- p - p
 Impl (Prop p) (Poss (Prop p)) :: PC

So the type says that this is a formula in the predicate calculus?
(Even though you combine two formulae of modal logics.)
Are you happy with that? Just wondering?
Also, are you fine to take the conjunction of a PC and Modal formula,
which is admitted by your types?
(If not, you may want to use phantom types.)

So it seems like the type doesn't carry a lot of information.
Then we could also use different types.
In particular, we could do without existentials.

The types we get will (additionally) record the arity of the outermost
constructor. (In your model, the type records the kind of logic
of the outermost constructor.)

class (Show f) = Formula f

data PC0 = Prop String
data Formula x = PC1 x   = Neg x
data (Formula x, Formula y) = PC2 x y = Conj x y | Disj x y | Impl x y

instance Formula PC0
instance Formula x = Formula (PC1 x)
instance (Formula x, Formula y) = Formula (PC2 x y)

instance Show PC0
  where
show (Prop s) = s

instance Formula x
  = Show (PC1 x)
  where
show (Neg x)  = ~ ++ show x

instance (Formula x, Formula y) 
  = Show (PC2 x y)
  where
show (Conj a b) = (show a) ++  /\\  ++ (show b)
show (Disj a b) = (show a) ++  \\/  ++ (show b)
show (Impl a b) = (show a) ++  -   ++ (show b)

data Formula x = Modal1 x = Poss x | Necc x

instance Formula x = Formula (Modal1 x)

instance Formula x = Show (Modal1 x)
  where
show (Poss a) =  ++ (show a)
show (Necc a) = [] ++ (show a)

main = do
  print (Prop p)
  print (Poss (Prop p))
  print (Impl (Prop p) (Poss (Prop p)))

(Again, just wondering whether this might be an Ok solution.)

Thomas Sutton wrote:
  In Java (C#, Python, etc) I'd do this ...

Please post your Java code.
I might want to add it to the OOHaskell demo suite.

Ralf


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Thomas Sutton
 Sent: Thursday, June 23, 2005 3:27 AM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Re: Using type classes for polymorphism of
 dataconstructors
 
 On 11/06/2005, at 11:18 PM, Thomas Sutton wrote:
  In Java (C#, Python, etc) I'd do this by writing an interface
  Formula and have a bunch of abstract classes (PropositionalFormula,
  ModalFormula, PredicateFormula, etc) implement this interface, then
  extend them into the connective classes Conjunction, Disjunction,
  etc. The constructors for these connective classes would take a
  number of Formula values (as appropriate for their arity).
 
  I've tried to implement this sort of polymorphism in Haskell using
  a type class, but I have not been able to get it to work and have
  begun to work on implementing this composition of logics in the
  DSL compiler, rather than the generated Haskell code. As solutions
  go, this is far from optimal.
 
  Can anyone set me on the right path to getting this type of
  polymorphism working in Haskell? Ought I be looking at dependant
  types?
 
 I've finally managed to find a way to get this to work using
 existentially quantified type variables and am posting it here for
 the benefit of the archives (and those novices like myself who will
 look to them in the future). My solution looks something like the
 following:
 
 A type class over which the constructors ought to be polymorphic:
 
   class (Show f) = Formula f where
   language :: f - String
 
 A type exhibiting such polymorphism:
 
   data PC
   = Prop String
   | forall a.   (Formula a)= Neg a
   | forall a b. (Formula a, Formula b) = Conj a b
   | forall a b. (Formula a, Formula b) = Disj a b
   | forall a b. (Formula a, Formula b) = Impl a b
   instance Formula PC where
   language _ = Propositional Calculus
   instance Show PC where
   show (Prop s)   = s
   show (Neg s)= ~ ++ (show s)
   show (Conj a b) = (show a) ++  /\\  ++ (show b)
   show (Disj a b) = (show a) ++  \\/  ++ (show b)
   show (Impl a b) = (show a) ++  -  ++ (show b)
 
 Another such type:
 
   data Modal
   = forall a. (Formula a) = Poss a
   | forall b. (Formula b) = Necc b
   instance Formula Modal where
   language _ = Modal Logic
   instance Show Modal where
   show (Poss a) =  ++ (show a)
   show (Necc a) = [] ++ (show a)
 
 Some example values of those types:
 
 Main :t (Prop p)-- p
 Prop p :: PC
 
 Main :t (Poss (Prop p))-- p
 Poss (Prop p) :: Modal
 
 Main :t (Impl (Prop p) (Poss (Prop p)))-- p - p
 Impl (Prop p) (Poss (Prop p)) :: PC
 
 I also have a sneaking suspicion I'd also be able to solve this
 problem using dependant types, but I have not investigated that
 approach.
 
 Cheers,
 Thomas Sutton
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Using type classes for polymorphism of data constructors

2005-06-14 Thread Thomas Sutton

On 13/06/2005, at 8:29 PM, Henning Thielemann wrote:

On Sat, 11 Jun 2005, Thomas Sutton wrote:

The end goal in all of this is that the user (perhaps a logician
rather than a computer scientist) will describe the calculus they
wish to use in a simple DSL. This DSL will then be translated into
Haskell and linked against some infrastructure implementing general
tableaux bits and pieces. These logic implementations ought to be
composable such that we can define modal logic to be propositional
calculus with the addition of [] and .


Is there a need for a custom DSL or will it be possible to express
theorems in Haskell?
Having used HOL a bit, I'm not sure that using a general PL as the  
user interface to a theorem prover is such a great idea. The goal of  
the project (an honours project) is to be able to construct  
[counter-] models using as wide a range of /labelled tableaux  
calculi/ as possible, thus the need for a DSL of some description (to  
specify each calculus).


The theorems themselves will be expressed using the operators  
described for each calculus (using the DSL). It will be, in essence,  
a meta theorem prover.



QuickCheck can test properties which are just Haskell
functions with random input, so it would be comfortable to use these
properties for proving, too. There is also the proof editor Alfa.  
As far

as know it is written in Haskell but the theorems are not expressed in
Haskell.
I've not looked at QuickCheck yet, though I've been meaning to get to  
it for quite a while; I'll have to bump it up the queue.


Cheers,
Thomas Sutton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using type classes for polymorphism of data constructors

2005-06-13 Thread Henning Thielemann

On Sat, 11 Jun 2005, Thomas Sutton wrote:

 The end goal in all of this is that the user (perhaps a logician
 rather than a computer scientist) will describe the calculus they
 wish to use in a simple DSL. This DSL will then be translated into
 Haskell and linked against some infrastructure implementing general
 tableaux bits and pieces. These logic implementations ought to be
 composable such that we can define modal logic to be propositional
 calculus with the addition of [] and .

Is there a need for a custom DSL or will it be possible to express
theorems in Haskell? QuickCheck can test properties which are just Haskell
functions with random input, so it would be comfortable to use these
properties for proving, too. There is also the proof editor Alfa. As far
as know it is written in Haskell but the theorems are not expressed in
Haskell.

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


[Haskell-cafe] Using type classes for polymorphism of data constructors

2005-06-11 Thread Thomas Sutton

Hi all,

I've just started working on a theorem prover (labelled tableaux in  
case anyone cares) in Haskell. In preparation, I've been attempting  
to define some data types to represent logical formulae. As one of  
the requirements of my project is generality (i.e. it must be easily  
extendible to support additional logics), I've been attempting to  
build these data types modularly.


The end goal in all of this is that the user (perhaps a logician  
rather than a computer scientist) will describe the calculus they  
wish to use in a simple DSL. This DSL will then be translated into  
Haskell and linked against some infrastructure implementing general  
tableaux bits and pieces. These logic implementations ought to be  
composable such that we can define modal logic to be propositional  
calculus with the addition of [] and .


In Java (C#, Python, etc) I'd do this by writing an interface Formula  
and have a bunch of abstract classes (PropositionalFormula,  
ModalFormula, PredicateFormula, etc) implement this interface, then  
extend them into the connective classes Conjunction, Disjunction,  
etc. The constructors for these connective classes would take a  
number of Formula values (as appropriate for their arity).


I've tried to implement this sort of polymorphism in Haskell using a  
type class, but I have not been able to get it to work and have begun  
to work on implementing this composition of logics in the DSL  
compiler, rather than the generated Haskell code. As solutions go,  
this is far from optimal.


Can anyone set me on the right path to getting this type of  
polymorphism working in Haskell? Ought I be looking at dependant types?


Thanks in advance,
Thomas Sutton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Simulating OO programming with type classes; writing a factory fu nction

2005-06-01 Thread oleg

Alistair Bayley wrote:

 There's a small problem: how to write a factory function that returns values
 of various subtypes. The makeSubType function below won't compile, obviously
 because the returns types are different (they're not the same 'm').

Indeed, expressions in both branches of an `if' statement

   if s == SubBase1
   then SubBase1 3
   else SubBase2 (SubBase1 4)

must be of the same type. If we had intersection types (I'm not
complaining!), the compiler would have derived the intersection by
itself. As things are now, we have to make the intersection manually:
we have to abstract away irrelevant pieces. Expressions
`SubBase1 3' and `SubBase2 (SubBase1 4)' have in common the fact that
both have types that are instances of a Method class. So, we have to
write that common piece of information explicitly. There are two ways
of doing this, which can be called direct style and CPS style. In
direct style, we do

 data WM = forall m. Method m = WM m
 makeSubType1 :: String - WM 
 makeSubType1 s =
   if s == SubBase1
   then WM $ SubBase1 3
   else WM $ SubBase2 (SubBase1 4)

 test1 = let foo x = case x of WM y - method2 y
 in map (foo . makeSubType1) [SubBase1, SubBase2]

The CPS style is just the inverse:

 -- Higher-ranked type: signature is required!
 makeSubType2:: (forall m. Method m = m - w) - String - w
 makeSubType2 consumer s =
   if s == SubBase1
   then consumer $ SubBase1 3
   else consumer $ SubBase2 (SubBase1 4)

 test2 = let foo x = method2 x
   in map (makeSubType2 foo) [SubBase1, SubBase2]

The CPS style involves less tagging (no need to add and remove the tag
WM). Also, the CPS style is more general:

 makeSubType1' s = makeSubType2 WM s

 test3 = let foo x = case x of WM y - method2 y
   in map (foo . makeSubType1') [SubBase1, SubBase2]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simulating OO programming with type classes; writing a factory fu nction

2005-05-31 Thread Bruno Oliveira
Hi Alistair!

Just a quick reply (I didn't had time to look at Ralf's technique).
Looking at your code, it seems to me that you are missing the notion of a 
supertype (perhaps, that's the intended thing with BaseClass?). 

I would use an existencial type to capture this notion:

===
data Base = forall c . Method c = Base c

instance BaseClass Base

instance Method Base where
  method1 (Base x) i = Base (method1 x i)
  method2 (Base x) = method2 x

the modifications on the code would be:

class BaseClass c = Method c where
  -- method1 returns a supertype Base
  method1 :: c - Int - Base
  method2 :: c - Int

instance Method c = Method (SubBase2 c) where
 -- method1 does not fail any more
  method1 x i = Base (SubBase2 (SubBase1 5))
  method2 x = 2

makeSubType s =
  if s == SubBase1
  then Base (SubBase1 3)
  else Base (SubBase2 (SubBase1 4))


Perhaps a better name for Base would be SuperMethod 
(since it is really trying to capture the fact that is the super 
type for Method).

Hope it helps

Cheers,

Bruno


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


Re: [Haskell-cafe] Re: Type classes and definite types

2005-05-11 Thread Krasimir Angelov
Hi Bryn Keller,

The solution for your problem is very simple. You just have to fetch
all values as strings. In this way the library will do all required
conversions for you.

printRow stmt = do
  id - getFieldValue stmt ID
  code - getFieldValue stmt Code
  name - getFieldValue stmt Name
 putStrLn (unwords [id, code, name])


Cheers,
  Krasimir


On 5/6/05, Bryn Keller [EMAIL PROTECTED] wrote:
 Max Vasin wrote:
 
 Bryn Keller [EMAIL PROTECTED] writes:
 
 
 
 Hi Max,
 
 
 Hello Bryn,
 
 
 
 Thanks for pointing this out. It's odd that I don't see that anywhere
 in the docs at the HToolkit site:
 http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC
 certainly believes it exists. However, this doesn't actually solve the
 problem. Substituting toSqlValue for show in printRow' gives the same
 compile error:
 
 Main.hs:22:18:
 Ambiguous type variable `a' in the constraint:
   `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30
 Probable fix: add a type signature that fixes these type variable(s)
 
 So, like with (show (read s)), we still can't use the function until
 we've established a definite type for the value, not just a type
 class.
 
 
 Yeah...
 Some more RTFSing shows that we have the
 
 getFieldValueType :: Statement - String - (SqlType, Bool)
 
 which allows us to write
 
 printRow stmt = do (id :: Int) - getFieldValue stmt ID
let (codeType, _) = getFieldValueType stmt Code
codestr - case codeType of
SqlChar _ - do (c :: String) - 
  getFieldValue stmt Code
return (toSqlValue c)
SqlInteger - do (i :: Int) - 
  getFieldValue stmt Code
 return (toSqlValue i)
-- etc for all SqlType data constructors
putStrLn (unwords [show id, codestr])
 
 At least it compiles. But it's ugly :-(
 
 
 Ah, good point! Ugly it may be, but at least it works. Thanks for the idea!
 
 Bryn
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Nice pedagogical examples of type classes?

2005-01-28 Thread Benjamin Pierce
My Advanced Programming course is quickly approaching the lectures on type
classes, and I am interested in finding a little more (beyond what's in SOE)
in the way of examples that illustrate nice uses (especially of more
advanced aspects of the class system).  I'd be most grateful for pointers to
people's favorites.

Examples should be reasonably small and depend only on Haskell 98 features.
I haven't discussed monads yet, but I'm also interested in good monadic
examples for later in the semester.

Many thanks,

- Benjamin

P.S.  Suggestions for interesting exercises along these lines are also
appreciated!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-29 Thread Sebastian Sylvan
On Tue, 14 Dec 2004 15:40:13 +, Keith Wansbrough
[EMAIL PROTECTED] wrote:
  On the other hand, it's difficult or impossible to make a list of a
  bunch of different types of things that have nothing in common save
  being members of the class.
 
 I've recently been playing with making, for each class C, a
 interface datatype IC (appropriately universally and existentially
 qualified so as to include a dictionary for class C), and then making
 this IC an instance of class C.  Then I can wrap any instance of C up
 in an IC, and make a list of those.
 

I think there should be standard syntax for this...
Some sort of operator for turning one or several type classes into an
interface datatype.

So you could write something like something like...

f :: Show,Num - [Show,Eq] - Eq,Num 
f a xs = ...

So the first parameter is just a value of the interface datatype
data ShowNum = forall a . (Show a, Num a)  = ShowNum a

And it's all automatically up and downcasted.

This is one of the more powerful idioms in languages such as Java
(collections of objects which satisfy some interface, for instance)
and should, IMO, be supported by some special syntax to facilitate
it's use in Haskell.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-29 Thread Keean Schupke
There are two ways to do the list of class members, existentials is one
way...
   data MyBox = forall a . MyClass a = MyBox a
   type MyClassList = [MyBox]
   f :: MyClassList - MyClassList
An alternative is to use a heterogeneous list (see the HList library):
   http://www.cwi.nl/~ralf/HList
This allows heterogeneous lists with static typing, which can be
constrained by a class as follows:
class MyClassList x
instance MyClassList HNil
instance (MyClassList l,MyClass v) = MyClassList (HCons v l)
The constraint MyClassList now implies a heterogeneous list of members
of MyClass:
   f :: (MyClassList l,MyClassList l') = l - l'
This represents a filter function on a heterogeneous list of class 
members - The
drawback is that the list must be statically typecheckable... If you 
require run-time
list construction from IO actions, then you want to use existentials.

   Keean
Sebastian Sylvan wrote:
On Tue, 14 Dec 2004 15:40:13 +, Keith Wansbrough
[EMAIL PROTECTED] wrote:
 

On the other hand, it's difficult or impossible to make a list of a
bunch of different types of things that have nothing in common save
being members of the class.
 

I've recently been playing with making, for each class C, a
interface datatype IC (appropriately universally and existentially
qualified so as to include a dictionary for class C), and then making
this IC an instance of class C.  Then I can wrap any instance of C up
in an IC, and make a list of those.
   

I think there should be standard syntax for this...
Some sort of operator for turning one or several type classes into an
interface datatype.
So you could write something like something like...
f :: Show,Num - [Show,Eq] - Eq,Num 
f a xs = ...

So the first parameter is just a value of the interface datatype
data ShowNum = forall a . (Show a, Num a)  = ShowNum a
And it's all automatically up and downcasted.
This is one of the more powerful idioms in languages such as Java
(collections of objects which satisfy some interface, for instance)
and should, IMO, be supported by some special syntax to facilitate
it's use in Haskell.
/S
 

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


Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-15 Thread Keean Schupke
See the HList library (http://www.cwi.ni/~ralf/HList) and use an HList
constrained by your interface.
   Keean.
John Goerzen wrote:
Hi,
I often have a situation where I'm designing specialized components to
do a more general task.   Examples could include mail folder code (maildir,
mbox, etc), configuration file parsing, protocol handlers for URL
accesses, logging backends, etc.
For some of these, I've used a data object with named fields, each one
of them being a function that performs various tasks (open connection to
the URL, read data, whatever.)  So, I get a standard interface.  The
advantage of this approach is that I can build a list containing all
sorts of different data objects in it.
For others, I've used typeclasses, and made the different specialized
components a member of the typeclass.  This seems to provide a cleaner
interface, and one that is more readily extended (maybe I want to
support IMAP folders, and support all its searching capabilities too).
On the other hand, it's difficult or impossible to make a list of a
bunch of different types of things that have nothing in common save
being members of the class.
Is there any advice on the best way to do these things?
Thanks,
John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


[Haskell-cafe] Named function fields vs. type classes

2004-12-14 Thread Derek Elkins
  On the other hand, it's difficult or impossible to make a list of a
  bunch of different types of things that have nothing in common save
  being members of the class.
 
 I've recently been playing with making, for each class C, a
 interface datatype IC (appropriately universally and existentially
 qualified so as to include a dictionary for class C), and then making
 this IC an instance of class C.  Then I can wrap any instance of C up
 in an IC, and make a list of those.
 
 The casts get a bit annoying, though; the compiler can't figure out
 that this IC is in some sense the maximum type in class C, and so
 can't resolve things like
 
 f :: MyClass a = [a] - b
 f = ...
 
 upcast :: MyClass a = a - IMyClass  -- usually defined as an
 instance of class Cast upcast x = IMyClass x
 
 f [upcast a, upcast b]  -- yields type error
 
 Instead, you have to redefine f as follows:
 
 f' :: [IMyClass] - b
 
 which is a bit annoying.
 
 HTH.
 
 --KW 8-)

Not surprisingly, the wiki
(http://www.haskell.org/hawiki/ExistentialTypes) has some discussion
about this as well, though not too much to add to what has been said.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Named function fields vs. type classes

2004-12-13 Thread John Goerzen
Hi,

I often have a situation where I'm designing specialized components to
do a more general task.   Examples could include mail folder code (maildir,
mbox, etc), configuration file parsing, protocol handlers for URL
accesses, logging backends, etc.

For some of these, I've used a data object with named fields, each one
of them being a function that performs various tasks (open connection to
the URL, read data, whatever.)  So, I get a standard interface.  The
advantage of this approach is that I can build a list containing all
sorts of different data objects in it.

For others, I've used typeclasses, and made the different specialized
components a member of the typeclass.  This seems to provide a cleaner
interface, and one that is more readily extended (maybe I want to
support IMAP folders, and support all its searching capabilities too).

On the other hand, it's difficult or impossible to make a list of a
bunch of different types of things that have nothing in common save
being members of the class.

Is there any advice on the best way to do these things?

Thanks,

John

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


Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-13 Thread Ralf Laemmel
Major apologies for this repeated plug for HList.
Anyway, HLists [1] are *exactly* designed for this sort of problem.
Well, one can also use existential quantification + bounded polymorphism;
with the shapes benchmark providing a good example [2]. The trade-offs are
explored a little bit on the OOHaskell slides and in the corresponding
code base [3].
Cheers,
Ralf
[1] http://homepages.cwi.nl/~ralf/HList/
[2] http://www.angelfire.com/tx4/cus/shapes/haskell.html
[3] http://homepages.cwi.nl/~ralf/OOHaskell/
John Goerzen wrote:
Hi,
I often have a situation where I'm designing specialized components to
do a more general task.   Examples could include mail folder code (maildir,
mbox, etc), configuration file parsing, protocol handlers for URL
accesses, logging backends, etc.
For some of these, I've used a data object with named fields, each one
of them being a function that performs various tasks (open connection to
the URL, read data, whatever.)  So, I get a standard interface.  The
advantage of this approach is that I can build a list containing all
sorts of different data objects in it.
For others, I've used typeclasses, and made the different specialized
components a member of the typeclass.  This seems to provide a cleaner
interface, and one that is more readily extended (maybe I want to
support IMAP folders, and support all its searching capabilities too).
On the other hand, it's difficult or impossible to make a list of a
bunch of different types of things that have nothing in common save
being members of the class.
Is there any advice on the best way to do these things?
Thanks,
John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-13 Thread Keith Wansbrough
 On the other hand, it's difficult or impossible to make a list of a
 bunch of different types of things that have nothing in common save
 being members of the class.

I've recently been playing with making, for each class C, a
interface datatype IC (appropriately universally and existentially
qualified so as to include a dictionary for class C), and then making
this IC an instance of class C.  Then I can wrap any instance of C up
in an IC, and make a list of those.

The casts get a bit annoying, though; the compiler can't figure out
that this IC is in some sense the maximum type in class C, and so
can't resolve things like

f :: MyClass a = [a] - b
f = ...

upcast :: MyClass a = a - IMyClass  -- usually defined as an instance of 
class Cast
upcast x = IMyClass x


f [upcast a, upcast b]  -- yields type error

Instead, you have to redefine f as follows:

f' :: [IMyClass] - b

which is a bit annoying.

HTH.

--KW 8-)

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


Low-level notation for type classes WAS: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Martin Sulzmann
Hi,

Daan said:

  
  Personally, I feel that this problem might be better solved by
  making a lot of the implicit assumptions (and semantics) of type
  classes more explicit, and bring them under user control. Of course,
  I do have not have any idea of how this should be done concretely ;-)
  
  (although type class directives might be a step in the right direction?)
  

Well, you might not need to look that far :)
To a great extent you can use Constraint Handling Rules (CHRs)
to explain type classes.

E.g., consider

Gregory J. Duck, Simon Peyton-Jones, Peter J. Stuckey and Martin Sulzmann  
Sound and Decidable Type Inference for Functional Dependencies

Peter J. Stuckey and Martin Sulzmann  
A Theory of Overloading


I've just skimmed through the Type Class Directives paper.
Pl correct me if I'm wrong but it appears that
the disjoint directive can be modeled by CHRs.

Example:

disjoint (Integral, Fractional)

can be encoded by

rule Integral a, Fractional a == False (1)

The never directive is in fact a special instance of disjoint.
E.g.,

never Num Bool

can be encoded by

rule Num Bool == False (2)

Note that the Chameleon type debugger provides type error explanation
support if the error is due to rule applications such as (1) and (2).

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


Derivable type classes bug?

2004-11-22 Thread Koen Claessen
Hi,

Take a look at the following program, making use of
derivable type classes.


module Bug where

import Data.Generics

class Foo a where
  foo :: a - Int
  foo{| Unit |}_ = 1
  foo{| a :*: b |} _ = 2
  foo{| a :+: b |} _ = 3

instance Foo [a]


GHC 6.2.2 produces the following error message:


Bug.hs:12:
Could not deduce (Foo a) from the context (Foo [a])
  arising from use of `foo' at Bug.hs:12


Why is the context needed? 'foo' is not a recursive
function?

I guess it is because the default declaration is split up
into several instances:


instance Foo Unit where
  foo _ = 1

instance (Foo a, Foo b) = Foo (a :*: b) where
  foo _ = 2

instance (Foo a, Foo b) = Foo (a :+: b) where
  foo _ = 3


Why not generating:


instance Foo Unit where
  foo _ = 1

instance Foo (a :*: b) where
  foo _ = 2

instance Foo (a :+: b) where
  foo _ = 3


when the context is not needed?

(My motivation is: I have a class like this:

  class Arbitrary a = Shrink a where
shrinkSub :: a - [a]
shrinkSub{| ... |} = ... shrink ...

The definition of shrinkSub is not recursive, it calls a
function 'shrink' from the Arbitrary class instead.)

Regards,
/Koen

PS. Has the implementation of Generics changed from some
earlier compiler version (GHC 5.xx)? I have code lying
around that I am almost certain of used to compile with an
earlier version of GHC (that I do not have access to
anymore).


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Derivable type classes bug?

2004-11-22 Thread Simon Peyton-Jones
Yes, you guessed right.  Your generic class declaration gives rise to
instance declarations like

| instance (Foo a, Foo b) = Foo (a :*: b) where
|   foo _ = 2

You suggest that it could be cleverer about guessing the context for the
instance decl, and that would make sense.  But this'd then be the *only*
time that the context of an instance decl was inferred, rather than
provided.  So (a) that's unusual (needs explanation etc), and (b) it'd
require some jiggling in the compiler, which is currently set up for
checking instance decls only.

An alternative, I guess, would be to ask the programmer to supply the
context for the instance decls.  But it's hard to see good syntax.  Were
would the context go in the class decl?

Another alternative could be for the programmer to give the
separated-out instance declarations himself, rather than having them
grouped in the class decl.  But we'd still need some way to signal that
the method should be generated generically. Something like

class Foo a where
  foo :: a - Int 
  generic foo   -- New keyword

instance Foo Unit where ...
instance Foo (a :+: b) where ...
etc

Signalling generic-ness like this could even allow generic-ness on a
method-by-method basis.  Kind of like specifying the default method.  I
don't want to eat another keyword, though.  And somehow it'd be better
if the same signal happened for the current case.  But
class Foo a where
  foo :: a - Int
  generic foo
  foo {| Unit |} = ...
seems rather heavy.   

So the possibilities are:

(A).  Infer the instance context.
(B).  Somehow specify the instance contexts in the class decl
(C).  Optionally, give separate instances for Unit, :+: etc, plus a
signal
in the class decl the default method is generic.  Syntax?

I think my preferences would go (C), (A), (B); if we could agree a
syntax for (C).  

Does anyone else have a (somewhat informed) opinion?

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-bugs-
| [EMAIL PROTECTED] On Behalf Of Koen Claessen
| Sent: 16 November 2004 17:17
| To: [EMAIL PROTECTED]
| Subject: Derivable type classes bug?
| 
| Hi,
| 
| Take a look at the following program, making use of
| derivable type classes.
| 
| 
| module Bug where
| 
| import Data.Generics
| 
| class Foo a where
|   foo :: a - Int
|   foo{| Unit |}_ = 1
|   foo{| a :*: b |} _ = 2
|   foo{| a :+: b |} _ = 3
| 
| instance Foo [a]
| 
| 
| GHC 6.2.2 produces the following error message:
| 
| 
| Bug.hs:12:
| Could not deduce (Foo a) from the context (Foo [a])
|   arising from use of `foo' at Bug.hs:12
| 
| 
| Why is the context needed? 'foo' is not a recursive
| function?
| 
| I guess it is because the default declaration is split up
| into several instances:
| 
| 
| instance Foo Unit where
|   foo _ = 1
| 
| instance (Foo a, Foo b) = Foo (a :*: b) where
|   foo _ = 2
| 
| instance (Foo a, Foo b) = Foo (a :+: b) where
|   foo _ = 3
| 
| 
| Why not generating:
| 
| 
| instance Foo Unit where
|   foo _ = 1
| 
| instance Foo (a :*: b) where
|   foo _ = 2
| 
| instance Foo (a :+: b) where
|   foo _ = 3
| 
| 
| when the context is not needed?
| 
| (My motivation is: I have a class like this:
| 
|   class Arbitrary a = Shrink a where
| shrinkSub :: a - [a]
| shrinkSub{| ... |} = ... shrink ...
| 
| The definition of shrinkSub is not recursive, it calls a
| function 'shrink' from the Arbitrary class instead.)
| 
| Regards,
| /Koen
| 
| PS. Has the implementation of Generics changed from some
| earlier compiler version (GHC 5.xx)? I have code lying
| around that I am almost certain of used to compile with an
| earlier version of GHC (that I do not have access to
| anymore).
| 
| 
| ___
| Glasgow-haskell-bugs mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[Haskell-cafe] wc again (Lists and type classes)

2004-10-15 Thread MR K P SCHUPKE

Have been playing with the idea of a list class like
the one I posted earlier... but now a bit streamlined.

I have implemented wc using this class and a nice buffer
list. The result is something 4 times slower than the
current language-shootout code, but is rather neater.

The restriction on getting the full speed of the current code
is the requirement to freeze the IOUArray to get it out of the
IO monad. This could be solved with an IOList type but this
would not be compatible with the types for a 'normal' list.

Here's the code for wc:
--
main :: IO ()
main = do
   l - hGetIList 4096 stdin
   print $ wc l ' ' 0 0 0

wc :: List l Word8 = l Word8 - Char - Int - Int - Int - (Int,Int,Int)
wc l p i j k
   | p `seq` i `seq` j `seq` k `seq` False = undefined
   | not $ Main.null l, h - (toEnum . fromEnum . Main.head) l, t - Main.tail l = 
case isSpace h of
  False - wc t h (i + 1) (j + if isSpace p then 1 else 0) k
  _ - wc t h (i + 1) j (k + if h == '\n' then 1 else 0)
   | otherwise = (i,j,k)
---

And here's the definition of the list class and instances 
(one is provided for a normal list for reference)

--
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module Main where

import Char
import GHC.IOBase
import System.IO
import Data.Word
import Data.Array.IO
import Data.Array.Unboxed

data IList a i e = ICons i i (a i e) (IList a i e) | INil

class List l e where
   nil :: l e
   null :: l e - Bool
   head :: l e - e
   tail :: l e - l e
   (+:) :: e - l e - l e

class List (l a i) e = ListPlus l a i e where
   (++:) :: a i e - l a i e - l a i e
   part :: a i e - i - l a i e - l a i e

infixr 9 +:
infixr 9 ++:

instance List [] e where
   nil = []
   null (_:_) = False
   null _ = True
   head (a:_) = a
   tail (_:l) = l
   a +: l = a:l

instance (IArray a e,Ix i,Num i) = List (IList a i) e where
   nil = INil
   null INil = True
   null _ = False
   head (ICons i _ a _) = a!i
   head _ = error head: empty list
   tail (ICons i j a l)
  | i  j = ICons (i+1) j a l
  | otherwise = l
   tail _ = error tail: empty list
   a +: l = ICons 0 0 (array (0,0) [(0,a)]) l

instance (IArray a e,Ix i,Num i) = ListPlus IList a i e where
   a ++: l
  | e = s = ICons s e a l
  | otherwise = l
  where ~(s,e) = bounds a
   part a i l
  | e = i = ICons s i a l
  | otherwise = l
  where ~(s,e) = bounds a

hGetIList :: Int - Handle - IO (IList UArray Int Word8)
hGetIList bufSize h = do
   mt - newArray_ (0,bufSize-1)
   ioLoop mt
   where

  ioLoop mt = unsafeInterleaveIO $ do
 sz - hGetArray h mt bufSize
 hd - freeze mt
 case sz of
0 - return nil
n  | n  bufSize - do
  return (part hd (n-1) nil)
   | otherwise - do
  tl - ioLoop mt
  return (hd ++: tl)
--

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


[Haskell-cafe] Re: wc again (Lists and type classes)

2004-10-15 Thread MR K P SCHUPKE

Of course when I say it's neater - I mean if the List class
were defined in the libraries, so only the short definition
of 'wc' given at the beginning of my last post would be required!

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


Extensible Serialization class with type classes

2004-08-26 Thread Simon David Foster
I've been trying to put together a type-class based serialization (XML)
for types in GHC. Essentially the serializer class takes the form

class Seriliazer a where
   serialize :: a - XmlFilter

This works very well, but I then wanted to make this system extensible,
so that for example for types which are also typed by equivalent XSD
Types (i.e. types with constraint XSDType a = a) could have their
type-data encoded into the tree. 

The problem is, it seems to me there is no viable method of adding an
extra parameter function to the serialiaze function, which will enforce
extra constraints on a and allow recursive serialization. Obviously
simply passing a function (C a = a - XmlFilter) doesn't work, since
the type a becomes unified to the top-level type and so can't be passed
down.

The second attempt was to add another type class called Hook, with two
type variables; the first being a dummy type and the second the variable
to represent the type being serialized;

class Hook a t where
hookAttr :: t - a - [(String, String)]
hookElem :: t - a - [XmlFilter]

and rewriting serialize as 

class Hook a t = Serializer a t where
serialize :: t - a - XmlFilter

Then, passing the dummy type to the serialized function as the t value
would force the extra constraints from its Hook instance on a. This
method though doesn't really work that well; first of all it requires
undecidable-instances and second each new instance on serialize requires
a humongous context since each type used directly and indirectly needs
inferring as an instance of Hook. The idea was that this code could be
generated automatically, and that really makes it too difficult to do.

The Third attempt was to use existential types to encapsulate a
constrained polymorphic type and use Typeable + Generics to choose
between a number of functions. This though doesn't work either, since
each value down the type tree needs to be of the appropriate monomorphic
existentially quantified type since polymorphic types aren't Typeable.

I seem to have pretty much exhausted every option for building this
extensible Serializer, and so my question is this; is there anyway of
passing a hook function to the serializer class instances, such that it
will remain polymorphic down the serialization tree but will also
enforce the constraints on the input parameter on the type being
serialized. For example is it every likely to be possible to reify
polymorphic types?

-Si.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell-cafe] Re: Extensible Serialization class with type classes

2004-08-26 Thread Ralf Laemmel
[redirected to Haskell-cafe from ghc...]
I think the point is not to define your class Seriliazer,
but to define it as a generic function instead. After all,
it is kind of show (because it is serialisation).
Reading your
earlier emails, it seems a remaining problem is to keep
this function somewhat open as to allow to special cases
afterwards. This is a nice topic. Here we go.
The normal serialisation function with a serialisation result
Q is of such a type
serialise :: Data a = a - Q
Internally such a function would be probably defined by
recursion such as
serialise = ... gmapQ serialise ...
In fact, some types would already be subject to special cases.
So we have
serialise = generic_case `extQ` specific_case1 `extQ` specific_case2 ...
where
 generic_case = ... gmapQ serialise ...
 specific_case1 = ... % do something for my favourite type
This is exactly the code skeleton of show.
Now the question is how to make the whole business extensible.
I normally do this with a type as follows:
extensible_serialise :: Data a = (forall b. Data b = b - Maybe Q) - 
a - Q

That is, there is an extra parameter for the type specific cases to
be ruled from the outside. Note the Maybe. Here, Nothing means that a
specific type is not handled by the parameter, so the normal serialise
has to be applied.
Regarding your other problem, optional types, this seems to be solvable 
as well.
Again, *don't* define this class

class XSDType a with
where xsdType :: a - String
  xsdNS :: a - String
...but rather define a generic function, this time is nothing but
a type case of type
forall x. Typeable x = x - Maybe (String, String)
Hope it helps.
Conclusion: don't use classes, rather use generic functions.
Ralf
Simon David Foster wrote:
On Thu, 2004-08-26 at 20:52, Ralf Laemmel wrote:
 

Hi Simon,
I think you should be able to succeed with Scrap your boilerplate.
(I am not sure that you need existentials.)
For the overall XmlIsh style of type erasue and type validation see the 
XmlIsh example at:
http://www.cs.vu.nl/boilerplate/
   

The main requirements for the XML serializer are;
1) It should be scalable; so users should be able to import a compile
module with the basic XML infrastructure and add serializers for new
Complex and Simple (i.e. leaf node) types.
2) It should be optionally typeable; there exists several systems for
typing an XML document, the most prominent of which is XSD. The main
requirement is that if the XML tree is to be typed, clearly each node in
the tree must be associated with mapping to an XSD name and name-space
(2 Strings) or some other data items if typing by another system. The
way I was planning on doing this was using a class; XSDType a with
functions xsdType :: a - String and xsdNS :: a - String. Then at
serialisation if a particular type and all it's constituent types were
XSD Typeable, extra data (i.e. an extra attribute type=nsp:name) can
(again optionally) be inserted into the tree.
The XmlIsh example uses a number of functions for serialising different
data-types down the tree. I'm not sure how scalable doing it this way
would be; can you integrate a type-class system with it? The other
problem is dealing with Schematic extensions, such as SOAP Arrays which
have the requirement that the elements are always typeable but should
not be part of the core serialiser.
My other question is, section 7 only mentions polymorphic types which
hold constraints Data, Typeable and Typeable1; can the new Generics deal
with other polymorphic constraints? This is the main problem; the
type-class system can deal fine with just serialisation of data-type
content, it just doesn't seem to be able to handle an optional
type-system.
Ideally I need to produce a system where one XML namespace maps to one
module and that module provides data-types, serialisers and typers for
the given XML types, such that other modules which use those data-types
themselves should be able to import that module and its serialisers to
(heuristically) build serialisers for itself.
-Si.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 


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


Re: [Haskell-cafe] Re: Fun with multi-parameter type classes

2004-08-21 Thread Sam Mason
karczma wrote:
Actually, I would like to know what was the purpose of all
that... 

I was writing some new code and wanted to break it into two parts,
they should have very little knowledge of each other other than what
methods are available in each (hence the classes).  The actual types
of the values that were being passed around should have remained
invisible to the other half of the code.

Anyway, I didn't want to dump loads of code on you so I rewrote it in
a simpler manner that took the form of the read and show.  The
actual implementations weren't supposed to be of importance, just the
fact that they were passing around something that the calling code
shouldn't have known about.

I've since realised that I can't solve the problem in the way I
originally wanted to and have now sort of turned the code inside out
so that there aren't any magically typed references floating around.

Hope that makes a bit more sense now,
  Sam
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fun with multi-parameter type classes

2004-08-20 Thread Henning Thielemann

On Thu, 19 Aug 2004, Sam Mason wrote:

class Foo t where
   encode :: String - t
   decode :: t - String
 
test = decode . encode
 
 This currently fails, because the type checker insists on trying
 to figure out what its type should be - even though it shouldn't
 be needed.


In contrast to that,

 test = encode . decode

should not fail. :-)

Btw. for my association of the names 'encode' and 'decode' the signatures
are the other way round, i.e.

   decode :: String - t
   encode :: t - String


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


[Haskell-cafe] Fun with multi-parameter type classes

2004-08-19 Thread Sam Mason
Hi,

I've been getting into Haskell over the past few months and have just
come up against a bit of a brick wall when trying to encapsulate
some of the data structures in my code nicely.  Basically what I
want to have, is a type class where one of the intermediate values
is opaque with respect to code using its implementations.  This is
a simplified version of what I'm trying to accomplish:

   class Foo t where
  encode :: String - t
  decode :: t - String

   instance Foo Int where
  encode = read
  decode = show

   test = decode . encode

This currently fails, because the type checker insists on trying
to figure out what its type should be - even though it shouldn't
be needed.

Any suggestions on how to encode this sort of thing?  And if it is
possible, can it be extended to multiple type parameters? as this is
really what I want to use it for.

About the only way I can think of fixing it, is by turning the
code inside out - sort of like the way an AST drives the compiler,
but without knowing how it represents things internally.

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


Re: [Haskell-cafe] Fun with multi-parameter type classes

2004-08-19 Thread Marius Nita
On Thu, Aug 19, 2004 at 05:42:10PM +0100, Sam Mason wrote:
 Hi,
 
 I've been getting into Haskell over the past few months and have just
 come up against a bit of a brick wall when trying to encapsulate
 some of the data structures in my code nicely.  Basically what I
 want to have, is a type class where one of the intermediate values
 is opaque with respect to code using its implementations.  This is
 a simplified version of what I'm trying to accomplish:
 
class Foo t where
   encode :: String - t
   decode :: t - String
 
instance Foo Int where
   encode = read
   decode = show
 
test = decode . encode
 
 This currently fails, because the type checker insists on trying
 to figure out what its type should be - even though it shouldn't
 be needed.

You could fix it by type-annotating encode:

  test = decode . (encode :: String-Int)

It makes sense that it doesn't work unannotated, since in the general
case, you'd have more than one instance of Foo. Certainly you wouldn't
want functions to stop working when you add one more instance.

I think this sort of abstract manipulation is only possible with
existential types. For example:

  data T = forall t.MkT (String - t) (t - String)

  x = MkT (read :: String-Int) show
  y = MkT (read :: String-Float) show

  test (MkT encode decode) = decode . encode

---

  *Main test x 0
  0
  *Main test y 6.7
  6.7

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


Re: [Haskell-cafe] Fun with multi-parameter type classes

2004-08-19 Thread Jon Cast
 Hi,
 
 I've been getting into Haskell over the past few months and have just
 come up against a bit of a brick wall when trying to encapsulate
 some of the data structures in my code nicely.  Basically what I
 want to have, is a type class where one of the intermediate values
 is opaque with respect to code using its implementations.  This is
 a simplified version of what I'm trying to accomplish:
 
class Foo t where
   encode :: String - t
   decode :: t - String
 
instance Foo Int where
   encode = read
   decode = show
 
test = decode . encode
 
 This currently fails, because the type checker insists on trying to
 figure out what its type should be - even though it shouldn't be
 needed.

The intermediate type /is/ needed---it's a (hidden) parameter to your
`encode' and `decode' functions.  Why do you think it shouldn't be?

snip

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


[Haskell-cafe] Re: Fun with multi-parameter type classes

2004-08-19 Thread karczma
Sam Mason writes: 

Jon Cast wrote:
The intermediate type /is/ needed---it's a (hidden) parameter to your
`encode' and `decode' functions.  Why do you think it shouldn't be?
Because I couldn't see the woods for the trees.  I think I had
almost figured out what I was asking (the impossible) before your
message appeared.
... 

Don't forget that this is the toplevel business, not a universal
disease. GHCi says 

Prelude :t (show . read)
(show . read) :: String - String 

and doesn't complain. But if you define 

bz = show . read 

the attempt to load this definition (file: ctest.hs) results in: 

ctest.hs:3:
  Ambiguous type variable `a' in these top-level constraints:
`Read a' arising from use of `read' at ctest.hs:5
`Show a' arising from use of `show' at ctest.hs:5
Failed, modules loaded: none.
Prelude 

So, as one of my friends used to say: it should be obvious for
everybody that what is obvious for one, need not be obvious for
the others... 

Jerzy Karczmarczuk 

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


Re: [Haskell-cafe] Re: Fun with multi-parameter type classes

2004-08-19 Thread Sam Mason
karczma wrote:
Don't forget that this is the toplevel business, not a universal
disease. GHCi says 

Prelude :t (show . read)
(show . read) :: String - String 

and doesn't complain. But if you define 

bz = show . read 

the attempt to load this definition (file: ctest.hs) results in: 

ctest.hs:3:
  Ambiguous type variable `a' in these top-level constraints:
`Read a' arising from use of `read' at ctest.hs:5
`Show a' arising from use of `show' at ctest.hs:5
Failed, modules loaded: none.
Prelude 

OK, you've got me interested!  Why doesn't GHCi complain about the
ambiguity?

So, as one of my friends used to say: it should be obvious for
everybody that what is obvious for one, need not be obvious for
the others... 

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


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-09 Thread Stefan Holdermans
Arjun,
  AG This class definition is giving me a lot of problems
  AG with the successor function:
 class (Ord st) = MinimaxState st where
successors :: st - [(action, st)]
terminal   :: st - Bool
 instance MinimaxState Int where
terminal i   = i == 0
successors i = [(1,i+1), (-1,i-1)]
See, http://www.haskell.org//pipermail/haskell-cafe/2004-July/006424.html.
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-09 Thread Stefan Holdermans
Arjan,
AG I'm curious as to why my class declaration
AG compiles in GHC, as there doesn't seem to
AG be any way to use it.
 class (Ord st) = MinimaxState st where
   successors :: forall a . st - [(a, st)]
   terminal   :: st - True
Any implementation of the successors method needs to produce values of 
an arbitrarely type a. Hence, it can only produce the empty list or a 
list of pairs that all have bottom as their first component.

 instance MinimaxState Bool where
   successors = const []
   terminal   = not
 instance MinimaxState Int where
   successors n = [(undefined, pred n), (undefined, succ n)]
   terminal 0   = True
   terminal n   = False
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Stefan Holdermans
Arjun,
  AG This class definition is giving me a lot of problems
  AG with the successor function:
 class (Ord st) = MinimaxState st where
   successors :: st - [(action, st)]
   terminal   :: st - Bool
 instance MinimaxState Int where
   terminal i   = i == 0
   successors i = [(1,i+1), (-1,i-1)]
See, http://www.haskell.org//pipermail/haskell-cafe/2004-July/006424.html.
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Arjun Guha
I'd rather not do that, but even if I did, the type-variable action 
would not be reachable in the terminal function.  I could specify a 
functional dependency st - action (though I've never used it, it would 
be a fun to learn).  I'm curious as to why my class declaration 
compiles in GHC, as there doesn't seem to be any way to use it.

-Arjun
On Aug 7, 2004, at 01:06, [EMAIL PROTECTED] wrote:
Hi Arjun.
How about inserting one more parameter, action, in your class 
definition:

class (Ord st) = MinimaxState st action where
   successors:: st - [(action,st)]
   terminal:: st - Bool
instance MinimaxState Int Int where
   terminal i = i == 0
   successors i = [(1,i+1), (-1,i-1)]
Then don't forget to start the compiler/interpreter with 
-fglasgow-exts.

Hope this helps.
Regards,
Carlos

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


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Stefan Holdermans
Arjan,
AG I'm curious as to why my class declaration
AG compiles in GHC, as there doesn't seem to
AG be any way to use it.
  class (Ord st) = MinimaxState st where
successors :: forall a . st - [(a, st)]
terminal   :: st - True
Any implementation of the successors method needs to produce values of
an arbitrarely type a. Hence, it can only produce the empty list or a
list of pairs that all have bottom as their first component.
  instance MinimaxState Bool where
successors = const []
terminal   = not
  instance MinimaxState Int where
successors n = [(undefined, pred n), (undefined, succ n)]
terminal 0   = True
terminal n   = False
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread camarao
 How about inserting one more parameter, action, in your class
 definition:
 class (Ord st) = MinimaxState st action where
successors:: st - [(action,st)]
terminal:: st - Bool
 instance MinimaxState Int Int where
terminal i = i == 0
successors i = [(1,i+1), (-1,i-1)]

 I'd rather not do that, but even if I did, the type-variable action
 would not be reachable in the terminal function.  I could specify a
 functional dependency st - action (though I've never used it, it would
 be a fun to learn).

Right... you need the functional dependency because of terminal, and in
general a type annotation for using it.

Carlos



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


[Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-06 Thread Arjun Guha
This class definition is giving me a lot of problems with the successor 
function:

class (Ord st) = MinimaxState st where
  successors:: st - [(action,st)]
  terminal:: st - Bool
A trivial example would be:
instance MinimaxState Int where
  terminal i = i == 0
  successors i = [(1,i+1), (-1,i-1)]
However, I get this error in GHC:
Could not deduce (Num action)
from the context (MinimaxState Int, Ord Int)
  arising from the literal `1' at AbTest.hs:7
Probable fix:
Add (Num action) to the class or instance method `successors'
In the first argument of `negate', namely `1'
In the list element: (- 1, (- i) - 1)
In the definition of `successors':
successors i = [(1, i + 1), (- 1, (- i) - 1)]
I have the class definition and the instance definition in seperate 
files.  I don't understand where I'm supposed to put the probable fix. 
 I don't want it to be in the class definition, since action should be 
fairly arbitrary.

In fact, no matter what I try, I get errors, for example:
instance MinimaxState Int where
  terminal i = i == 0
  successors i = [(action,i+1), (action,i-1)]
Cannot unify the type-signature variable `action'
with the type `[Char]'
Expected type: action
Inferred type: [Char]
In the list element: (action, i + 1)
In the definition of `successors':
successors i = [(action, i + 1), (action, (- i) - 1)]
Any suggestions?
-Arjun
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Separate Namespaces and Type Classes

2004-07-09 Thread S.M.Kahrs

 one should be able to define two instances having the same signature, as 
 long as they are in different namespaces
[snip]
 But now, ghc complains about two instances of Foo Integer, although 
 there should be none in the namespace main.

It's a Haskell problem, not a ghc one.

Class instances are not constrained by module boundaries.
Other people have found this to be a problem,
e.g. in combination with tools like Strafunski - you just
cannot encapsulate a class instance in a module.

It's a design flaw in Haskell.

 I have not found any documentation on why ghc behaves like this and 
 whether this conforms to the haskell language specification.
 Is there any haskell compiler out there that is able to compile the 
 above example?

I think Clean (a very similar language) permits to limit the scope
of class instances.

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


[Haskell] Separate Namespaces and Type Classes

2004-07-08 Thread Stephan Herhut
Hi all,
I am pretty new to haskell, but while exploring the haskell module 
system, I came along some questions. As far as I found out, haskell 
supports separated namespaces, i.e. every module has its own symbol 
space. Thus, when defining a class in one module like

module A(Foo(f)) where
class Foo a where
 f ::  a - Integer
one should be able to define two instances having the same signature, as 
long as they are in different namespaces

module B(bar) where
import A(Foo(f))
instance Foo Integer where
 f x = x
bar x = f x
module C(tango)
import A(Foo(f))
instance Foo Integer where
 f x = x + 1
tango x = f x
As the integer instances of Foo are in separate modules and thus 
namespaces, one should be able to just import bar and tango

module Main(main)
import B(bar)
import C(tango)
main = print( (bar 5) + (tango 4) )
But now, ghc complains about two instances of Foo Integer, although 
there should be none in the namespace main.
I have not found any documentation on why ghc behaves like this and 
whether this conforms to the haskell language specification.
Is there any haskell compiler out there that is able to compile the 
above example?

Thanks for your help
Stephan
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Separate Namespaces and Type Classes

2004-07-08 Thread Ketil Malde
Stephan Herhut [EMAIL PROTECTED] writes:

 module B(bar) where
 instance Foo Integer where

 module C(tango)
 instance Foo Integer where

 import B(bar)
 import C(tango)

 But now, ghc complains about two instances of Foo Integer, although
 there should be none in the namespace main.

I suspect the problem is that instances are always exported and
imported, so that GHC sees both in Main, and complains.  Perhaps this
could be relaxed to allow your situation (where the class isn't used
directly in Main anyway)?

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


Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-13 Thread Ronny Wichers Schreur
Duncan Coutts writes (to the Haskell Mailing list):

I'm trying to write a generic curry ( uncurry) function that works for
functions of any arity.
See http://www.haskell.org/pipermail/haskell/2003-April/011720.html
where oleg presents a (ghc-specific) solution.
Cheers,

Ronny Wichers Schreur
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Duncan Coutts
Hi All,

I'm trying to write a generic curry ( uncurry) function that works for
functions of any arity. I have a couple solutions that nearly work, both
involving type classes.

Here's the first one:

class Curry tupled curried where
  genericCurry   :: tupled - curried
  genericUncurry :: curried - tupled

The base case is obvious:

instance Curry ((a,b) - c) (a - b - c) where
  genericCurry   f   x y  = f (x,y)
  genericUncurry f' (x,y) = f' x y

However, the inductive case is more tricky. We cannot generically create
tuples of arbitrary size so we'll have to make do with left (or right)
nested pairs. This nesting leads to problems later and for starters
requires overlapping instances:

instance Curry (   (b,c)  - d) ( b - c - d) =
 Curry ((a,(b,c)) - d) (a - b - c - d) where
  genericCurry   f  a  b c   = f (a,(b,c))
  genericUncurry f (a,(b,c)) = f  a  b c

This works, but when we come to use it we often run into cases where the
type checker complains with messages such as:
No instance for (Curry ((Int, Int) - Int) (a - b - Int))
I guess that this is because it fails to be able to convince itself that
a  b are Int, in which case there would be an instance. This can be
solved by supplying enough type annotations, however this is annoying
and part of the point of a generic curry is that we don't know the arity
of the function to which we are applying it.

So I thought that functional dependencies might help because the curried
type should uniquely determine the uncurried type (and vice versa).
However if I change the class declaration to:

class Curry tupled curried | tupled - curried, curried - tupled  where
  genericCurry   :: tupled - curried
  genericUncurry :: curried - tupled

Then the compiler complains about my instance declarations:

Functional dependencies conflict between instance declarations:
  ./Curry.hs:11:0: instance Curry ((a, b) - c) (a - b - c)
  ./Curry.hs:16:0:
instance (Curry ((b, c) - d) (b - c - d)) =
 Curry ((a, (b, c)) - d) (a - b - c - d)

I don't fully understand why this is the case, but it is to do with the
nested pairing, because individual instance declarations for 3-tuples,
4-tuples work find.

Any insight or suggestions would be interesting.

Duncan

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


Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Malcolm Wallace
Duncan Coutts [EMAIL PROTECTED] writes:

 So I thought that functional dependencies might help because the curried
 type should uniquely determine the uncurried type (and vice versa).
 However if I change the class declaration to:
 
 class Curry tupled curried | tupled - curried, curried - tupled  where
   genericCurry   :: tupled - curried
   genericUncurry :: curried - tupled
 
 Then the compiler complains about my instance declarations:
 
 Functional dependencies conflict between instance declarations:
   ./Curry.hs:11:0: instance Curry ((a, b) - c) (a - b - c)
   ./Curry.hs:16:0:
 instance (Curry ((b, c) - d) (b - c - d)) =
  Curry ((a, (b, c)) - d) (a - b - c - d)
 
 I don't fully understand why this is the case, but it is to do with the
 nested pairing, because individual instance declarations for 3-tuples,
 4-tuples work fine.

With a little alpha-renaming:

instance Curry ((a, b) - c) (a - b - c)

instance (Curry ((e, f) - g) (e - f - g)) =
  Curry ((d, (e, f)) - g) (d - e - f - g)

It should be fairly easy to see that the type
  (d, (e, f)) - g
is an instance of
  (a, b) - c
where a==d and b==(e,f) and c==g.  Also
  (d - e - f - g)
is an instance of
  (a - b - c)
where a=d and b==e and c==(f-g).  So for one thing your two instances
overlap, but additionally, the type-variables do not unify, because
in the tupled part of the Curry predicate, b==(e,f), but in the curried
part of the predicate, b==e.

Regards,
Malcolm
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Esa Pulkkinen

In message [EMAIL PROTECTED], Duncan Coutts writes:
I'm trying to write a generic curry ( uncurry) function that works for
functions of any arity. I have a couple solutions that nearly work, both
involving type classes.
[SNIP]
Any insight or suggestions would be interesting.

Here's one solution, which I think is more general than what you ask,
but I guess it should work as well. It's based on adjunctions from
category theory:

class (Functor path, Functor space) =
Adjunction path space | path - space, space - path where
  leftAdjunct :: (path top - bot) - top - space bot
  unit :: top - space (path top) 
  rightAdjunct :: (top - space bot) - path top - bot
  counit :: path (space bot) - bot 
  -- minimum required impl: unit xor leftAdjunct
  -- minimum required impl: counit xor rightAdjunct
  unit = leftAdjunct id
  leftAdjunct f = fmap f . unit
  counit = rightAdjunct id
  rightAdjunct g = counit . fmap g

-- Here are some instances for different arities:

instance Adjunction ((,) a) ((-) a) where
 unit t = \arg - (arg,t)
 counit (x,f) = f x

newtype Func2 a b c = Func2 (a - b - c)
   -- Func2 is only needed due to syntax of partial type constructor application

instance Adjunction ((,,) a b) (Func2 a b) where
  unit t = Func2 (\arg1 arg2 - (arg1,arg2,t))
  counit (arg1,arg2,Func2 f) = f arg1 arg2

instance Functor ((,,) a b) where
  fmap f (x,y,z) = (x,y,f z)

instance Functor (Func2 a b) where
  fmap f (Func2 g) = Func2 (\a b - f (g a b))

Here, 'leftAdjunct' is a generalization of curry and rightAdjunct is a
generalization of uncurry.
-- 
  Esa Pulkkinen
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Generics and type classes

2004-02-02 Thread Simon Peyton-Jones
What you ask is not easy.  When you ask for
everywhere special
you ask to apply special to each node of the tree -- and special
requires the MyClass dictionary.  But the library code for 'gmapT' and
'everywhere' don't know about MyClass.  In particular, to do (gmapT
special), poor old gmapT has to find a MyClass dictionary to pass to
each call to special -- and it has no way to do that. 

I bet that you could do what you want by replacing the 'instance MyClass
ExampleType1' by mkTs for special, so special uses run-time type
dispatch to implement the operations in MyClass.  I guess that's what
Keeane is suggesting.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of MR K P SCHUPKE
| Sent: 02 February 2004 11:48
| To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
| Subject: Re: Generics and type classes
| 
| Because the 'cast' operator used in generics, works on having a
concrete
| type to cast to. What you need to do is:
| 
| module TypeTest where
| 
| import Data.Generics
| 
| class Data a = MyClass a
| 
| instance MyClass ExampleType1
| instance MyClass ExampleType2
| 
| special :: ExampleType1 - ExampleType1
| special = ...
| 
| special2 :: ExampleType2 - ExampleType2
| special2 = ...
| 
| generic :: MyClass a = a - a
| generic = everywhere (mkT special `extT` special2 ...)
| 
|   Regards,
|   Keean.
| ___
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type classes confusion

2004-01-10 Thread andrew cooke

Hi,

I'm trying to use type classes and suspect I've got confused somewhere
down the line, because I've got to an error message that I don't
understand and can't remove.

I have a class that works like a hash table, mapping from String to some
type.  I have two instances, one that is case insensitive for keys.  I
want to hide these instances from the rest of the code, which should only
use the class.  This class is called Dictionary.

In addition, for Dictionaries that map Strings to Strings, I have some
functions which do substitutions on Strings using their own contents. 
Possibly the first source of problems is that I can't find a way to
express these two classes together without multiple parameter type classes
(one parameter for the case/no case and one for the type returned):

class Dictionary d a where
  add'   :: d a - (String, a) - d a
  ...

instance Dictionary DictNoCase a where
  add' d (k, v) = ...

-- Dict is the underlying tree implementation and Maybe stores the
-- value for the null (empty string) key.
data DictNoCase a = DictNoCase (Dict a) (Maybe a)

class (Dictionary d String) = SubDictionary d where
  substitute :: d String - String - String
  ...

instance SubDictionary DictNoCase where
  substitute d s = ...

All the above compiles and seems correct (is it?).

I also provide an empty instance of the two instance types.  For
DictNoCase, this is
empty = DictCase Empty Nothing
where Empty is the empty type constructor for Dict

Now (almost there) elsewhere I want to define a data type that contains
two of these Dictionaries.  One stores String values.  The other stores
functions that take this same type and return a result and a copy of the
type:

data Context s f = (Dictionary s String, Dictionary f (CustomFn s f)) =
Ctx {state :: s String,
 funcs :: f (CustomFn s f)}

type CustomFn s f = Context s f - Arg - IO (Context s f, Result s f)

data Result s f = Attr Name String
| Repeat (CustomFn s f)
...

newContext = Ctx empty emptyNC

(where empty is the case-sensitive empty dictionary)

Now THAT doesn't compile:

Template.lhs:60:
All of the type variables in the constraint `Dictionary s
String' are
already
in scope
(at least one must be universally quantified here)
When checking the existential context of constructor `Ctx'
In the data type declaration for `Context'

Template.lhs:60:
All of the type variables in the constraint `Dictionary f
(CustomFn s
f)' are
already in scope
(at least one must be universally quantified here)
When checking the existential context of constructor `Ctx'
In the data type declaration for `Context'

where line 60 is data Context

And I can't see what I've done wrong.  Any help gratefully received.

Cheers,
Andrew

-- 
personal web site: http://www.acooke.org/andrew
personal mail list: http://www.acooke.org/andrew/compute.html
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Type classes confusion

2004-01-10 Thread andrew cooke

Ah.  I just need to drop the context from the data type declaration.

Sorry,
Andrew

andrew cooke said:

 Hi,

 I'm trying to use type classes and suspect I've got confused somewhere
 down the line, because I've got to an error message that I don't
 understand and can't remove.

 I have a class that works like a hash table, mapping from String to some
 type.  I have two instances, one that is case insensitive for keys.  I
 want to hide these instances from the rest of the code, which should only
 use the class.  This class is called Dictionary.

 In addition, for Dictionaries that map Strings to Strings, I have some
 functions which do substitutions on Strings using their own contents.
 Possibly the first source of problems is that I can't find a way to
 express these two classes together without multiple parameter type classes
 (one parameter for the case/no case and one for the type returned):

 class Dictionary d a where
   add'   :: d a - (String, a) - d a
   ...

 instance Dictionary DictNoCase a where
   add' d (k, v) = ...

 -- Dict is the underlying tree implementation and Maybe stores the
 -- value for the null (empty string) key.
 data DictNoCase a = DictNoCase (Dict a) (Maybe a)

 class (Dictionary d String) = SubDictionary d where
   substitute :: d String - String - String
   ...

 instance SubDictionary DictNoCase where
   substitute d s = ...

 All the above compiles and seems correct (is it?).

 I also provide an empty instance of the two instance types.  For
 DictNoCase, this is
 empty = DictCase Empty Nothing
 where Empty is the empty type constructor for Dict

 Now (almost there) elsewhere I want to define a data type that contains
 two of these Dictionaries.  One stores String values.  The other stores
 functions that take this same type and return a result and a copy of the
 type:

 data Context s f = (Dictionary s String, Dictionary f (CustomFn s f)) =
 Ctx {state :: s String,
  funcs :: f (CustomFn s f)}

 type CustomFn s f = Context s f - Arg - IO (Context s f, Result s f)

 data Result s f = Attr Name String
 | Repeat (CustomFn s f)
 ...

 newContext = Ctx empty emptyNC

 (where empty is the case-sensitive empty dictionary)

 Now THAT doesn't compile:

 Template.lhs:60:
 All of the type variables in the constraint `Dictionary s
 String' are
 already
 in scope
 (at least one must be universally quantified here)
 When checking the existential context of constructor `Ctx'
 In the data type declaration for `Context'

 Template.lhs:60:
 All of the type variables in the constraint `Dictionary f
 (CustomFn s
 f)' are
 already in scope
 (at least one must be universally quantified here)
 When checking the existential context of constructor `Ctx'
 In the data type declaration for `Context'

 where line 60 is data Context

 And I can't see what I've done wrong.  Any help gratefully received.

 Cheers,
 Andrew

 --
 personal web site: http://www.acooke.org/andrew
 personal mail list: http://www.acooke.org/andrew/compute.html
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell




-- 
personal web site: http://www.acooke.org/andrew
personal mail list: http://www.acooke.org/andrew/compute.html
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: type classes, superclass of different kind

2003-12-11 Thread Johannes Waldmann
Robert Will wrote:

Note that in an OO programming language with generic classes ...

(We shouldn't make our functional designs more different from the OO ones, 
 than they need to be.)

why should *we* care :-)

more often than not, OO design is resticted and misleading.

you see how most OO languages jump through funny hoops (in this case, 
generics) because they just lack proper higher-order types.

good luck with your library. but make sure you study existing (FP) 
designs, e. g. Chris Okasaki's Edison:
http://www.eecs.usma.edu/Personnel/okasaki/pubs.html#hw00
--
-- Johannes Waldmann,  Tel/Fax: (0341) 3076 6479 / 6480 --
-- http://www.imn.htwk-leipzig.de/~waldmann/ -

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


RE: type classes, superclass of different kind

2003-12-11 Thread Niklas Broberg
Robert Will wrote:

Now I would like to have Collection to be a superclass of Map yielding the
following typing
reduce :: (Map map a b) =
  ((a, b) - c) - c
  - map a b - c
Note that in an OO programming language with generic classes (which is in
general much less expressive than real polymorphism), I can write
class MAP[A, B] inherit COLLECTION[TUPLE[A, B]]

which has exactly the desired effect (and that's what I do in the
imperative version of my little library).
There seems to be no direct way to achieve the same thing with Haskell
type classes (or any extension I'm aware of).  Here is a quesion for the
most creative of thinkers: which is the design (in proper Haskell or a
wide-spread extension) possibly include much intermediate type classes and
other stuff, that comes nearest to my desire?
I don't know if I qualify as the most creative of thinkers, but I have a 
small library of ADSs that you may want to look at, it's at

http://www.dtek.chalmers.se/~d00nibro/algfk/

I recall having much the same problem as you did, my solution was to make 
maps (or Assoc as I call them) depend on tuple types, i.e. (somewhat 
simplified):

class (Collection c (k,v), Eq k) = Assoc c k v where
 lookup :: k - c (k,v) - v
 [...many more member functions here...]
This means that the type constructors for maps and collections have the same 
kind (* - *), which makes it possible for me to say that an Assoc is 
actually also a Collection. A lot more info to be found off the link.

I believe this question to be important and profound.  (We shouldn't
make our functional designs more different from the OO ones, than they
need to be.)  If I err, someone will tell me :-
No need to recreate all the stupid things the OO world has come up with, 
better to do it correctly right away... ;)

/Niklas Broberg, d00nibro[at]dtek.chalmers.se

_
The new MSN 8: advanced junk mail protection and 2 months FREE* 
http://join.msn.com/?page=features/junkmail

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


Re: type classes, superclass of different kind

2003-12-11 Thread David Sankel
--- Robert Will [EMAIL PROTECTED] wrote:
--  Here
--  is a quesion for the
--  most creative of thinkers: which is the design
(in
--  proper Haskell or a
--  wide-spread extension) possibly include much
--  intermediate type classes and
--  other stuff, that comes nearest to my desire?

Hello,

  I've often wondered the same thing.  I've found that
one can simulate several OO paradigms.  Note that
these aren't particularly elegant or simple.


Using Data Constructors:


 data Shape = Rectangle {topLeft :: (Int, Int),
bottomRight :: (Int,Int) } 
| Circle {center :: (Int,Int), radius ::
Int } 

This allows you have a list of shapes 

 shapeList :: [Shape]
 shapeList = [ Rectangle (-3,3) (0,0), Circle (0,0) 3
]

When you want member functions, you need to specialize
the function for
all the constructors.

 height :: Shape - Int
 height (Rectangle (a,b) (c,d)) = b - d
 height (Circle _ radius) = 2 * radius

Disadvantages:

1) When a new Shape is needed, one needs to edit the
original Shape source 
file.
2) If a member function is not implemented for a shape
subclass, it will lead
to a run-time error (instead of compile-time).

Advantages:

1) Simple Syntax
2) Allows lists of Shapes
3) Haskell98

Example: GHC's exception types
 
http://www.haskell.org/ghc/docs/latest/html/base/Control.Exception.html


Using Classes


Classes can be used to force a type have specific
functions to act upon it.
From our previous example:

 class Shape a where
   height :: a - Int

 data Rectangle = Rectangle {topLeft :: (Int, Int),
bottomRight :: (Int,Int) }
 data Circle = Circle {center :: (Int,Int), radius ::
Int } 
 
 instance Shape Circle where
   height (Circle _ radius) = 2 * radius

 instance Shape Rectangle where
   height (Rectangle (a,b) (c,d)) = b - d

In this case, something is a shape if it specifically
has the member 
functions associated with Shapes (height in this
case).

Advantages
1) Simple Syntax
2) Haskell98
3) Allows a user to easily add Shapes without
modifying the original source.
4) If a member function is not implemented for a shape
subclass, it will lead
to a compile-time error.

Disadvantages:
1) Lists of Shapes not allowed

Example: Haskell 98's Num class. 
http://www.haskell.org/ghc/


Classes with Instance holder.


There have been a few proposals of ways to get around
the List of Shapes 
problem with classes.  The Haskell98 ways looks like
this

 data ShapeInstance = ShapeInstance { ci_height ::
Int }

 toShapeInstance :: (Shape a) = a - ShapeInstance
 toShapeInstance a = ShapeInstance { ci_height =
(height a) }

 instance Shape ShapeInstance where
   height (ShapeInstance ci_height) = ci_height

So when we want a list of shapes, we can do

 shapeList = [ toShapeInstance (Circle (3,3) 3), 
   toShapeInstance (Rectangle (-3,3)
(0,0) ) ]

Of course this also has it's disadvantages.  Everytime
a new memeber function is added, it must be noted in
the ShapeInstance declaration, the toShapeInstance
function, and the instance Shape ShapeInstance
declaration.

Using a haskell extention, we can get a little better.
 Existentially quantified data constructors gives us
this:

 data ShapeInstance = forall a. Shape a =
ShapeInstance a
 
 instance Shape ShapeInstance where
   height (ShapeInstance a) = height a

 shapeList = [ ShapeInstance (Circle (3,3) 3), 
   ShapeInstance (Rectangle (-3,3) (0,0)
) ]

The benefits of this method are shorter code, and no
need to update the ShapeInstance declaration every
time a new member function is added.


Records extention


A different kind of inheritance can be implemented
with enhanced haskell 
records.  See
http://research.microsoft.com/~simonpj/Haskell/records.html
and
http://citeseer.nj.nec.com/gaster96polymorphic.html
for in depth explinations.  I'm not sure if these have
been impemented or not, but it would work as follows.

The inheritance provided by the above extentions is
more of a data inheritance 
than a functional inheritance. Lets say all shapes
must have a color parameter:

 type Shape = {color :: (Int,Int,Int)}
 type Circle = Shape + { center :: (Int,Int), radius
:: (Int) }
 type Rectangle = Shape + { topLeft :: (Int,Int),
bottomRight :: (Int, Int) }

So now we can reference this color for any shape by
calling .color.

 getColor :: (a : Shape ) - a - (Int,Int,Int)
 getColor a = a.color

I'm not sure how the records extention could be used
with Classes with instance 
holders to provide an even more plentiful OO
environment.

So I'll conclude this email with the observation that
Haskell supports some
OO constructs although not with the most elegance.

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


Re: type classes, superclass of different kind

2003-12-11 Thread Brandon Michael Moore


On Thu, 11 Dec 2003, Robert Will wrote:

 Hello,

 As you will have noticed, I'm designing a little library of Abstract Data
 Structuresm here is a small excerpt to get an idea:

 class Collection coll a where
 ...
 (+) :: coll a - coll a - coll a
 reduce :: (a - b) - b
   - coll a - b
 ...

 class Map map a b where
 ...
 (+) :: map a b - map a b - map a b
 at :: map a b
   - a - b
 ...

 Note that the classes don't only share similar types, they also have
 similar algebraic laws: both + and + are associative, and neither is
 commutative.

 Now I would like to have Collection to be a superclass of Map yielding the
 following typing

 reduce :: (Map map a b) =
   ((a, b) - c) - c
   - map a b - c

Functional dependencies will do this.

class Collection coll a | coll - a where
...
(+) :: coll - coll - coll
reduce :: (a - b - b) - b - coll - b
...

class (Collection map (a,b)) = Map map a b | map - a b where
...
(+) :: map - map - map
at :: map - a - b

Now you make instances like

instance Collection [a] a where
   (+) = (++)
   reduce = foldr

instance (Eq a) = Map [(a,b)] a b where
   new + old = nubBy (\(x,_) (y,_) - x == y) (new ++ old)
   at map x = fromJust (lookup x map)


 Note that in an OO programming language with generic classes (which is in
 general much less expressive than real polymorphism), I can write

 class MAP[A, B] inherit COLLECTION[TUPLE[A, B]]

 which has exactly the desired effect (and that's what I do in the
 imperative version of my little library).

This isn't exactly the same thing. In the OO code the interface
collections must provide consists of a set of methods. A particular
type, like COLLECTION[INTEGER] is the primitive unit that can implement
or fail to implement that interface.

In the Haskell code you require a collection to be a type constructor that
will give you a type with appropriate methods no matter what you apply
it to (ruling out special cases like extra compace sequences of booleans
and so on). A map is not something that takes a single argument and makes
a collection, so nothing can implement both of your map and collection
interfaces.

The solution is simple, drop the spurrious requirement that collections
be type constructors (or that all of our concrete collection types were
created by applying some type constructor to the element type). The
classes with functional dependencies say just that, our collection type
provides certain methods (involving the element types).

Collections were one of the examples in Mark Jones' paper on
functional dependencies (Type Classes with Functional Dependencies,
linked from the GHC Extension:Functional Dependencies section of the
GHC user's guide).

 There seems to be no direct way to achieve the same thing with Haskell
 type classes (or any extension I'm aware of).  Here is a quesion for the
 most creative of thinkers: which is the design (in proper Haskell or a
 wide-spread extension) possibly include much intermediate type classes and
 other stuff, that comes nearest to my desire?

 I believe this question to be important and profound.  (We shouldn't
 make our functional designs more different from the OO ones, than they
 need to be.)  If I err, someone will tell me :-

What problems do objects solve? They let you give a common interface to
types with the same functionality, so you can make functions slightly
polymorphic in any argument type with the operations your code needs.
They organize your state. Then let you reuse code when you make a new
slightly different type. Am I missing anything here?

I think type classes are a much better solution than inheritance for
keeping track of which types have which functionality. (at least the way
interface by inheritance works in most typed and popular object oriented
languages.)

Inheritance only really works for notions that only involve the type doing
the inheriting, or are at least heavly centered around that type. I don't
think Functor can be represented as an interface, or at least not a very
natural one. Most langauges I know of (see Nice for an exception)  also
require you to declare the interface a class supports when you declare it,
which is really painful when you want your code to work with types that
were around before you were, like defining a class to represent
marshallable values for interface/serialization code.

Are there any advantages to inheritance for managing interfaces? Maybe
it takes a few minutes less to explain the first time around. It's
probably easier to implement. Beyond that, I see nothing. Any creative
thinkers want to try this? (An answer here would motivate an extension
to the type class system, of course).

Brandon

 Robert

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


Re: Hypothetical reasoning in type classes

2003-11-23 Thread Ken Shan
On 2003-11-13T13:19:28-, Simon Peyton-Jones wrote:
 | From: [EMAIL PROTECTED]
 | 
 | Has anyone thought about adding hereditary Harrop formulas, in other
 | words hypothetical reasoning and universal quantification, to the
 | instance contexts in the Hsakell type class system?
 
 Yes, absolutely.  See
   http://research.microsoft.com/~simonpj/Papers/derive.htm
 Section 7, and Trifanov's paper at the Haskell Workshop 2003

Thanks for the pointers!  I am now thinking about encoding SML-style
module systems into Haskell using type classes with functional
dependencies.  For this purpose, I seem to need hereditary Harrop
formulas in instance contexts.  I wonder if such encodings have been
proposed previously in the literature?  The closest I was able to find
is Kahl and Scheffczyk's paper at the 2001 Haskell Workshop.

Thanks again,
Ken

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Anytime I see something screech across a room and latch onto someones
neck, and the guy screams and tries to get it off, I have to laugh,
because what is that thing.
[http://philip.greenspun.com/humor/deep-thoughts]


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


Re: Hypothetical reasoning in type classes

2003-11-16 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Ken Shan [EMAIL PROTECTED] wrote:

 Just today (and not
 only today) I wanted to write instance definitions like
 
 instance (forall a. C a = D a) = E [a] where ...

I've wanted this for awhile, in both class and instance declarations.

-- 
Ashley Yakeley, Seattle WA

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


Hypothetical reasoning in type classes

2003-11-13 Thread Ken Shan
Hello,

Has anyone thought about adding hereditary Harrop formulas, in other
words hypothetical reasoning and universal quantification, to the
instance contexts in the Hsakell type class system?  Just today (and not
only today) I wanted to write instance definitions like

instance (forall a. C a = D a) = E [a] where ...

This is analogous to wanting to write a rank-2 dictionary constructor

(forall a. C a - D a) - E [a]

at the term level, but with type classes, this dictionary constructor
should be applied automatically, in a type-directed fashion, at compile
time.  The theory behind such instance contexts doesn't seem so
intractable; indeed it looks decidable to my cursory examination.  The
opreational intuition is that we would like the type checker to generate
an eigenvariable a and perform hypothetical reasoning.

I would also like to quantify universally over type classes; in other
words, if ? is the kind of a type class constraint (aka a dictionary
type; perhaps o would be a better choice of notation), then I would
like to define not just types of kind *-*-? (aka type classes) or
kind (*-*)-? (aka constructor classes), but also types of kind
(*-?)-(*-?).  But that's for another day...

Ken

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Hi, my name is Kent, and I let people change my .sig on the internet.
Hi, Ken!
Put midgets back in midget porn! -- Not authorized by Ken Shan. Supported by
the association of midget porn workers, Local 9823.


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


RE: Hypothetical reasoning in type classes

2003-11-13 Thread Simon Peyton-Jones
Yes, absolutely.  See
http://research.microsoft.com/~simonpj/Papers/derive.htm
Section 7, and Trifanov's paper at the Haskell Workshop 2003

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Ken
| Shan
| Sent: 13 November 2003 05:40
| To: [EMAIL PROTECTED]
| Subject: Hypothetical reasoning in type classes
| 
| Hello,
| 
| Has anyone thought about adding hereditary Harrop formulas, in other
| words hypothetical reasoning and universal quantification, to the
| instance contexts in the Hsakell type class system?  Just today (and
not
| only today) I wanted to write instance definitions like
| 
| instance (forall a. C a = D a) = E [a] where ...
| 
| This is analogous to wanting to write a rank-2 dictionary constructor
| 
| (forall a. C a - D a) - E [a]
| 
| at the term level, but with type classes, this dictionary constructor
| should be applied automatically, in a type-directed fashion, at
compile
| time.  The theory behind such instance contexts doesn't seem so
| intractable; indeed it looks decidable to my cursory examination.  The
| opreational intuition is that we would like the type checker to
generate
| an eigenvariable a and perform hypothetical reasoning.
| 
| I would also like to quantify universally over type classes; in other
| words, if ? is the kind of a type class constraint (aka a dictionary
| type; perhaps o would be a better choice of notation), then I would
| like to define not just types of kind *-*-? (aka type classes) or
| kind (*-*)-? (aka constructor classes), but also types of kind
| (*-?)-(*-?).  But that's for another day...
| 
|   Ken
| 
| --
| Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
| Hi, my name is Kent, and I let people change my .sig on the
internet.
| Hi, Ken!
| Put midgets back in midget porn! -- Not authorized by Ken Shan.
Supported by
| the association of midget porn workers, Local 9823.


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


Re: Beta Reduction, undefined vs Type Classes

2003-11-10 Thread Keith Wansbrough
  class Thing t where
thing :: t
[..]
 Can someone please explain why
 
  fst (1,thing)
 
 ...gets an 'ambiguous type variable' error, but
 
  fst (1,undefined)
 
 ...doesn't? And is there anything I can change to make the former work
 as well? Even modifying fst doesn't work:

This kind of thing is a bit of a trap for young players.  You'll get errors when 
entering things into the interactive toplevel (hugs/ghci), but if you put it in a 
program you will almost certainly not get the errors, because more information will be 
available to the compiler from a full program than from a toy example.

The problem is that the member function thing doesn't take anything of type t by 
which the compiler might infer which instance it is.  You can see this even more 
easily by typing

  []

into ghci.

To fix it, give it a type annotation:

fst (1,thing::Thing Int)
([]::[Double])

for example.

The reason you don't get the error for fst (1,undefined) is because undefined has the 
perfectly good type (forall a. a), and so (1,undefined) has type (forall a. 
(Integer,a)) and fst (1,undefined) has type Integer.  Polymorphism (like the type of 
undefined) is much better behaved than overloading (like the types of thing).

It's actually more complicated than this, though - 1 actually has type Num a = a, but 
Haskell has a built-in defaulting rule which says that anything of this type should 
default to Integer or Double, in that order.  So you don't get ambiguity errors for 
simple numbers.  This makes life simpler when using Haskell as a calculator.

HTH.

--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: Beta Reduction, undefined vs Type Classes

2003-11-10 Thread Brian Boutel
Jared Warren wrote:

Consider:

 

class Thing t where
 thing :: t
instance Thing Int where
 thing = 0
instance Thing Char where
 thing = 'a'
   

Can someone please explain why

 

fst (1,thing)
   

...gets an 'ambiguous type variable' error, but

 

fst (1,undefined)
   

...doesn't? 

Perhaps because thing has an ambiguous type (it's either Int of Char), 
but undefined doesn't, (it's for all a.a).

Remember that type inference in the Haskell type system does not assume 
knowledge of the semantics of functions. In order to deduce the type of 
an application of fst, you need to determine the type of its argument 
- you can't discard one of ithe tuple components just because you know 
you will lose it when you apply a projection function. Type checking is 
done before any evaulation, compile-time or run-time.

You might argue that it would be a good idea to apply some program 
transformations early to avoid this kind of unnecessary ambiguity, but I 
have doubts about its general usefullness.

And is there anything I can change to make the former work
as well? Even modifying fst doesn't work:
 

fst' :: Thing b = (a,b) - a
fst' (~a,~b) = a
   

 

You should not expect it to work. The problem is with the type 
ambiguity, not with the semantics of fst.

--brian



--
Brian Boutel
Wellington New Zealand
Note the NOSPAM

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


Beta Reduction, undefined vs Type Classes

2003-11-09 Thread Jared Warren
Consider:

 class Thing t where
   thing :: t

 instance Thing Int where
   thing = 0

 instance Thing Char where
   thing = 'a'

Can someone please explain why

 fst (1,thing)

...gets an 'ambiguous type variable' error, but

 fst (1,undefined)

...doesn't? And is there anything I can change to make the former work
as well? Even modifying fst doesn't work:

 fst' :: Thing b = (a,b) - a
 fst' (~a,~b) = a

-- 
~ Jared Warren [EMAIL PROTECTED]
Computing Science, Queen's University

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


Type classes question

2003-08-29 Thread Eugene Nonko
Title: Type classes question






Hello,


I am trying to define class Dual and few instances as follows:


===

class Dual a where

 dual :: a - a


instance Dual Bool where

 dual = not


instance (Dual a, Dual b) = Dual (a - b) where

 dual f = dual . f . dual


instance Dual a = Dual [a] where

 dual = reverse . map dual


instance Num a = Dual a where

 dual = negate

===


For some reason Hugs does not lake the last definition saying 'ERROR dual.hs:13 - syntax error in instance head (constructor expected)'. What am I doing wrong?

-- Eugene





Type classes and code generation

2003-06-17 Thread Bayley, Alistair
I had a discussion with someone over the type class mechanism and would like
to clarify something.

When I compile this trivial program:

 module Main where
 main = putStrLn (show (1 + 2))

with ghc -Wall, the compiler says:

Main.lhs:3:
Warning: Defaulting the following constraint(s) to type `Integer'
 `Num a' arising from the literal `2' at Main.lhs:3

This implies to me that the compiler is generating the code for (+) for the
particular instance, rather than using a run-time dispatch mechanism to
select the correct (+) function. Is this correct, or am I way off? Does the
compiler *always* know what the actual instances being used are? Is there
some way of preventing the type mechanism from generating code for the
instance type, as opposed to the class? 


If I am correct, does it work the same way across module boundaries? (I
would think so.) If a module exports a class but no instances for that
class, then a user of that class would have to install their own instances.
OTOH, if the class plus one or more instances were exported, then a user
could use the supplied instance types, and the compiler would still generate
code to use the specific instances.


*
The information in this email and in any attachments is 
confidential and intended solely for the attention and use 
of the named addressee(s). This information may be 
subject to legal professional or other privilege or may 
otherwise be protected by work product immunity or other 
legal rules.  It must not be disclosed to any person without 
our authority.

If you are not the intended recipient, or a person 
responsible for delivering it to the intended recipient, you 
are not authorised to and must not disclose, copy, 
distribute, or retain this message or any part of it.
*

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


Re: Type classes and code generation

2003-06-17 Thread Bernard James POPE
 I had a discussion with someone over the type class mechanism and would like
 to clarify something.
 
 When I compile this trivial program:
 
  module Main where
  main = putStrLn (show (1 + 2))
 
 with ghc -Wall, the compiler says:
 
 Main.lhs:3:
 Warning: Defaulting the following constraint(s) to type `Integer'
`Num a' arising from the literal `2' at Main.lhs:3
 
 This implies to me that the compiler is generating the code for (+) for the
 particular instance, rather than using a run-time dispatch mechanism to
 select the correct (+) function. Is this correct, or am I way off? 

Hi,

I hope I've understod your question.

What this message is telling you is that the compiler is applying Haskell 98's
defaulting mechanism.

The numeric literals 1 and 2 in the code are overloaded, that is
they have type: Num a = a

When the program is run the calls to '+' and 'show' must be resolved to
particular instances. However the overloading of their arguments prevents
that. The overloading is thus ambiguous.

Haskell 98 has a rule that (very roughly) says when overloading is ambiguous
and it involves standard numeric classes, apply some defaults to resolve the
ambiguity. In this case the default rule is to resolve the outstanding
constraint 'Num a' with Integer (making the type of 1 and 2 Integer).

After defaulting the instances of + and show can be resolved. 

You can change the behaviour of defaulting, and even turn it off, try:

   module Main where 
   default ()
   ...

Compiling again with -Wall gives:

Ambiguous type variable(s) `a' in the constraint `Num a'
arising from the literal `2' at Foo.hs:6
In the second argument of `(+)', namely `2'
In the first argument of `show', namely `(1 + 2)'

You can also get the same effect as defaulting by putting explicit type
annotations in your program:

main = putStrLn (show ((1 + 2) :: Integer)) 

The Haskell Report doesn't say a whole lot about _how_ to implement the
type class overloading, though from what I understand,
most implementations use a similar algorithm (dictionary passing).

You can read all about typical implementations in the literature.
Google for Type Class, Implementation, and maybe even Haskell.

 Does the compiler *always* know what the actual instances being used are? 

A smart compiler can specialise the calls to overloaded functions in
circumstances when the type(s) of its arguments are also known. This is a
good thing because it tends to reduce the cost of overloading at runtime.

More aggresive forms of specialisation are also possible and discussed in
the literature.

I think if you look up the papers on implementing type classes your
questions should be answered. Mail me if you need some references.

Cheers,
Bernie.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Type classes and code generation

2003-06-17 Thread Keith Wansbrough
Alistair Bayley writes:

 Warning: Defaulting the following constraint(s) to type `Integer'
`Num a' arising from the literal `2' at Main.lhs:3
 
 This implies to me that the compiler is generating the code for (+) for the
 particular instance, rather than using a run-time dispatch mechanism to
 select the correct (+) function. Is this correct, or am I way off?  Does the
 compiler *always* know what the actual instances being used are?

Yes, roughly.  In Haskell, the compiler always figures out the types of 
everything at compile time.  This means it can often figure out which 
bit of code to use at compile time as well - but because of 
polymorphism, not always.  Consider this bit of code:

double :: Num a = a - a
double x = x + x

The function double will work on any type in the class Num, so the 
compiler can't know which + function to use.  But it *doesn't* solve 
this by run-time dispatch, like in C++.  Instead, it compiles double 
like this:

double' :: NumDict a - a - a
double' d x = let f = plus d
  in x `f` x

where NumDict is a record a bit like this:

data NumDict a = NumDict { plus :: a - a - a,
   minus :: a - a - a,
   fromInteger :: Integer - a
   ...
 }

NumDict is called a dictionary, and any time double' is called, the 
caller must supply the right dictionary.  If you write

double 2.0

then the compiler sees that you've written a Double, and so supplies 
the NumDict Double dictionary:

double' doubleNum 2.0

where doubleNum :: NumDict Double contains the methods for adding 
Doubles, subtracting them, and converting from Integers to them.

Whenever it can, a good optimising compiler (like GHC) will try to 
remove these extra dictionary applications, and use the code for the 
right method directly.  This is called specialisation.

Getting back to your original question, there's a little subtlety in 
Haskell to do with literals.  Whenever you type an integer literal like 
2, what the compiler actually sees is fromInteger 2.  fromInteger 
has type Num a = Integer - a, so this means that when you type an 
integer literal it is automatically converted to whatever numeric type 
is appropriate for the context.  In the context you give, there's still 
not enough information - it could be Int, or Integer, or Double, or 
several other things.  Another little subtlety called defaulting (see 
the Haskell 98 Report, in section 4.3.4) arranges that in this 
situation, the compiler will assume you mean Integer if that works, and 
failing that, it will try Double before giving up.  That's what the 
warning message you give is telling you.

 Is there
 some way of preventing the type mechanism from generating code for the
 instance type, as opposed to the class? 

I don't understand this question - does the explanation above help?

 If I am correct, does it work the same way across module boundaries? (I
 would think so.)

Yes, it does work automatically across instance boundaries.

 If a module exports a class but no instances for that
 class, then a user of that class would have to install their own instances.

Instance exporting is not easy to control in Haskell; if you export a 
type, then all its instances are exported along with it automatically.

 OTOH, if the class plus one or more instances were exported, then a user
 could use the supplied instance types, and the compiler would still generate
 code to use the specific instances.

From the explanation above, you should see that the compiler generates
polymorphic code for any function with a type class in its type (e.g.,
Num a = ...), and it's the *caller* that supplies the code for the
specific instances (the dictionary).  But if the type is known at
compile time, then the compiler will fill in the dictionary itself,
and may even specialise it away.

The intention is that there is only one, global instance space - you
can't tightly control the export or not of specific instances, they
are pretty much always exported and all visible.  This isn't quite
true in practice, but it's the idea.

Hope this helps.

If you don't mind, I'm going to put this conversation up on the Wiki,
at

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

--KW 8-)

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


RE: Type classes and code generation

2003-06-17 Thread Bayley, Alistair
  Is there
  some way of preventing the type mechanism from generating 
 code for the
  instance type, as opposed to the class? 
 
 I don't understand this question - does the explanation above help?


I could have been clearer with my questions. What I was wondering was: is
there some situation where the compiler can't statically determine the type
to be used?


 The function double will work on any type in the class Num, so the 
 compiler can't know which + function to use.

When it's applied, the compiler will know the types of the arguments, won't
it?. Which means that you would generate a version of double for each
(applied) instance of Num. I don't doubt that there's a good reason this is
not done: code bloat? or are there simply some expressions that can't be
statically resolved?

I suppose I was thinking: is the language design sufficiently clever that
it's *always* possible for the compiler to infer the type instance in use,
or are there some situations where it's not possible to infer the instance,
so some kind of function dispatch mechanism is necessary?


 Yes, roughly.  In Haskell, the compiler always figures out 
 the types of 
 everything at compile time.  This means it can often figure out which 
 bit of code to use at compile time as well - but because of 
 polymorphism, not always.  Consider this bit of code:
 
 double :: Num a = a - a
 double x = x + x
 
 The function double will work on any type in the class Num, so the 
 compiler can't know which + function to use.  But it *doesn't* solve 
 this by run-time dispatch, like in C++.  Instead, it compiles double 
 like this:
 
 double' :: NumDict a - a - a
 double' d x = let f = plus d
   in x `f` x
 
 where NumDict is a record a bit like this:
 
 data NumDict a = NumDict { plus :: a - a - a,
minus :: a - a - a,
  fromInteger :: Integer - a
  ...
  }
 
 NumDict is called a dictionary, and any time double' is called, the 
 caller must supply the right dictionary.  If you write
 
 double 2.0
 
 then the compiler sees that you've written a Double, and so supplies 
 the NumDict Double dictionary:
 
 double' doubleNum 2.0
 
 where doubleNum :: NumDict Double contains the methods for adding 
 Doubles, subtracting them, and converting from Integers to them.


This looks like a dispatching mechanism to me. However, I think I see that
this can still be done at compile-time. When double is applied to 2.0, the
compiler generates the double' doubleNum 2.0 code, which is still statically
resolvable. The advantage seems to be that you don't generate a double
function for each Num instance.

Does this also mean that a dictionary class is created for every class, and
a dictionary created for every instance?




 Getting back to your original question, there's a little subtlety in 
 Haskell to do with literals.  Whenever you type an integer 
 literal like  2, what the compiler actually sees is fromInteger 2.
 Another little subtlety called  defaulting (see 
 the Haskell 98 Report, in section 4.3.4) arranges that in this 
 
I knew about the fromInteger and similar treatment of literals, but the
defaulting system is news to me. I've skimmed over the Haskell report, but
details like this never sink in until you encounter them in practice...

 
 Instance exporting is not easy to control in Haskell; if you export a 
 type, then all its instances are exported along with it automatically.

Thanks. I wasn't sure how the export mechanism worked with regard to classes
and instances; I just took a (wrong) guess that you could control export of
classes and types separately.


*
The information in this email and in any attachments is 
confidential and intended solely for the attention and use 
of the named addressee(s). This information may be 
subject to legal professional or other privilege or may 
otherwise be protected by work product immunity or other 
legal rules.  It must not be disclosed to any person without 
our authority.

If you are not the intended recipient, or a person 
responsible for delivering it to the intended recipient, you 
are not authorised to and must not disclose, copy, 
distribute, or retain this message or any part of it.
*

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


Re: Type classes and code generation

2003-06-17 Thread Andreas Rossberg
Bayley, Alistair wrote:
When it's applied, the compiler will know the types of the arguments, won't
it?. Which means that you would generate a version of double for each
(applied) instance of Num. I don't doubt that there's a good reason this is
not done: code bloat? or are there simply some expressions that can't be
statically resolved?
I suppose I was thinking: is the language design sufficiently clever that
it's *always* possible for the compiler to infer the type instance in use,
or are there some situations where it's not possible to infer the instance,
so some kind of function dispatch mechanism is necessary?
This almost is an FAQ. Short answer: in general it is impossible to 
determine statically which instances/dictionaries are needed during 
evaluation. Their number may even be infinite. The main reason is that 
Haskell allows polymorphic recursion.

Consider the following (dumb) example:

f :: Eq a = [a] - Bool
f [] = True
f (x:xs) = x == x  f (map (\x - [x]) xs)
The number of instances used by f depends on the length of the argument 
list! Determining that statically is of course undecidable. If the list 
is infinite, f will use infinitely many instances (potentially, 
depending on lazy evaluation).

Another (non-Haskell-98) feature that prevents static resolution of type 
class dispatch are existential types, which actually provide the 
equivalent to real OO-style dynamic dispatch.

Of course, for most practical programs, the optimization you have in 
mind would be possible. I doubt compilers generally do it globally, 
though, because it requires whole program analysis, i.e. does not 
interfer well with separate compilation (beside other reasons).

| Andreas

--
Andreas Rossberg, [EMAIL PROTECTED]
Computer games don't affect kids; I mean if Pac Man affected us
 as kids, we would all be running around in darkened rooms, munching
 magic pills, and listening to repetitive electronic music.
 - Kristian Wilson, Nintendo Inc.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Type classes and code generation

2003-06-17 Thread Keith Wansbrough
 Does this also mean that a dictionary class is created for every class, and
 a dictionary created for every instance?

Yes, exactly.  Every class is translated to a data type declaration, 
and every instance is translated to an element of that data type - a 
dictionary.  (Note that you can't actually write those declarations in 
Haskell 98 in general, because they can have polymorphic fields; but 
this is a simple extension to the language).

Take a look at one of the references Bernard put on the bottom of the
Wiki page I just created for further information.

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

--KW 8-)

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


Re: Type classes and code generation

2003-06-17 Thread Hal Daume III
(Moved to the Cafe)

 Yes, exactly.  Every class is translated to a data type declaration, 
 and every instance is translated to an element of that data type - a 
 dictionary.  (Note that you can't actually write those declarations in 
 Haskell 98 in general, because they can have polymorphic fields; but 
 this is a simple extension to the language).

Keith, could you elaborate on this parenthetical?  Under what
circumstances can you not create the dictionary datatype for a class in
Haskell 98 (where the class itself is H98 :P)?

 - Hal

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


Re: Type classes and code generation

2003-06-17 Thread Keith Wansbrough
 You need to change the first line to this:
 
  data C a = C { pair :: forall b. b - (b,a) }
 
 and then it works fine (with -fglasgow-exts).  But you've now stepped
 outside the bounds of Haskell 98.

(oops, replying to myself... sure sign of madness! :) )

I hasten to add that this is *not* the same as existential quantification; note 
carefully the location of the forall wrt the constructor.

--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: Type classes problem: Could not deduce ...

2003-03-10 Thread Matthias Neubauer
Hi Dirk,

[EMAIL PROTECTED] writes:

 Hello, 
 
 trying to compile the following program
 
   class ClassA a where
   foo :: a - Int
 
   class ClassA a = ClassB b a where
   toA :: b - a
 
   test :: (ClassB b a) = b - Int
   test x = 
   let y = toA x in
   let z = foo y in
   z
 
 I get a compilation error:
 
   TestTypeClasses.hs:12:
 Could not deduce (ClassB b a1) from the context (ClassB b a)
 Probable fix:
   Add (ClassB b a1) to the type signature(s) for `test'
 arising from use of `toA' at TestTypeClasses.hs:12
 In a pattern binding: toA x
 
 Can anybody explain the problem to me or suggest workarounds? Adding
 (ClassB b a1) to the context does not solve the problem, it just
 generates an error of the same sort.

Consider the type of the following application of toA:

*Dirk :t toA (42::Int)
forall a. (ClassB Int a) = a

The type inference can't deduce much about the result type of the
application because type classes only specify relations over types. In
your case, ClassB is a binary relation over types. Hence, you could
easily imagine having two instances for ClassB

  instance ClassB Int Bool
  instance ClassB Int Char

putting the Int type into relation with more than a single other type.

Judging from your member function toA, I guess you'd really like to
say, that every type b of ClassB *uniquely determines* the second type
a. This can be expressed by a type class with functional
dependency[1]:

   class ClassA a = ClassB b a | b - a where
   toA :: b - a

Cheers,

Matthias

[1] Mark P Jones, Type Classes with Functional Dependencies, ESOP 2000

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: type classes vs. multiple data constructors

2003-02-17 Thread Andrew J Bromage
G'day.

On Mon, Feb 17, 2003 at 01:44:07AM -0500, Mike T. Machenry wrote:

  I was wondering if it's better to define them as type classes with the
 operations defined in the class. What do haskellian's do?

I can't speak for other Haskellians, but on the whole, it depends.

Here's the common situation: You have a family of N abstractions.  (In
your case, N=2.)  The abstractions are similar in some ways and
different in some ways.  The most appropriate design depends largely
on what those similarities and differences are.

From your definitions, it seems clear that there is some common
structure.  That suggests that a vanilla type class solution may
not be appropriate, because type classes do not directly support
common structure, only related operations.

Your solution wasn't bad:

 data PlayerState =
   FugitiveState {
 tickets :: Array Ticket Int,
 fHistory :: [Ticket] } |
   DetectiveState {
 tickets :: Array Ticket Int,
 dHistory :: [Stop] }

If the operations on the tickets field are different, or the
algorithms which operate on PlayerState are different for the
FugitiveState case and the DetectiveState case, this may be a good
design, because by not sharing structure, you're explicitly denying
any similarity (i.e. just because look the similar, that doesn't mean
they are similar).

If they are similar, then this may not be an appropriate design.
Ideally, you want to use language features and/or idioms which expose
the similarities (where they exist) and the differences (where they
exist).

Here's one design where the structural similarity is explicit:

data PlayerState
  = PlayerState {
tickets :: Array Ticket Int,
role:: RoleSpecificState
}

data RoleSpecificState
  = FugitiveState  { fHistory :: [Ticket] }
  | DetectiveState { dHistory :: [Stop] }

Depending on how similar the operations on the RoleSpecificState are
(say, if they are related by a common type signature, but have little
code in common), or if you want a design which is extensible to other
kinds of player (possibly at dynamic-link time) you may prefer to use
type classes to implement the role-specific states instead:

-- Warning: untested code follows

class RoleSpecificState a where
{- ... -}

data FugitiveState = FugitiveState { fHistory :: [Ticket] }

instance RoleSpecificState FugitiveState where
{- ... -}

data DetectiveState = DetectiveState { fHistory :: [Ticket] }

instance RoleSpecificState DetectiveState where
{- ... -}

data PlayerState
  = forall role. (RoleSpecificState role) =
PlayerState {
tickets :: Array Ticket Int,
role:: role
}

(If you know anything about design patterns, you may recognise this as
being similar to the Strategy pattern.  This is no accident.)

It's hard to say what is the most appropriate design without looking at
the algorithms and operations which act on the PlayerState type and
analysing their similarities and differences.

 Oh and if I say
 Instance Foo Baz where
   ...
 
 and only define a few of the operations in Foo... bdoes Baz take on some
 default methods?

If you've declared default methods, yes.

Cheers,
Andrew Bromage
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



type classes vs. multiple data constructors

2003-02-16 Thread Mike T. Machenry
I have a type that is as follows:

data PlayerState =
  FugitiveState {
tickets :: Array Ticket Int,
fHistory :: [Ticket] } |
  DetectiveState {
tickets :: Array Ticket Int,
dHistory :: [Stop] }

I have a few functions that act on PlayerState.

move :: PlayerState - PlayerState
move DetectiveState ... =
move FugitivieState ... =

 I was wondering if it's better to define them as type classes with the
operations defined in the class. What do haskellian's do? Oh and if I say
Instance Foo Baz where
  ...

and only define a few of the operations in Foo... bdoes Baz take on some
default methods?

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



Dispatch on what? (Was: seeking ideas for short lecture on type classes)

2003-02-04 Thread Jerzy Karczmarczuk
This is a somewhat older thread, but I ask you to enlighten me.

Norman Ramsey wrote:

A fact that I know but don't understand the implication of is that
Haskell dispatches on the static type of a value, whereas OO languages
dispatch on the dynamic type of a value.  But I suspect I'll leave
that out :-)



Dean Herington:

Perhaps I misunderstand, but I would suggest that fact is, if not 
incorrect, at least oversimplified.  I would say Haskell dispatches on the
dynamic type of a value, in the sense that a single polymorphic function
varies its behavior based on the specific type(s) of its argument(s).
What may distinguish Haskell from typical OO languages (I'm not an expert
on them) is that in Haskell such polymorphic functions could (always or at
least nearly so) be specialized statically for their uses at different types.


Fergus Henderson wrote:
 I agree.  The above characterization is highly misleading.  It would be
 more accurate and informative to say that both Haskell and OO languages
 dispatch on the dynamic type of a value.





Now my brain ceased to understand... Are you sure that OO dispatch schemas
are based on the *argument* type?

I would say that - unless I am dead wrong, the OO languages such as Smalltalk
do not dispatch on dynamic types of a value. The receiver is known, so its vir.
f. table (belonging to the receiver's class) is known as well, the dispatching
is based on the *message identifiers* independently of subsidiary arguments.
Only after that - perhaps - some reversions, message propagation depending on
the arg(s) value(s), etc. may take place, but all this is irrelevant...
Forgive me if I write stupidities.


Jerzy Karczmarczuk




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



Re: Dispatch on what? (Was: seeking ideas for short lecture on type classes)

2003-02-04 Thread John Hörnkvist

On Tuesday, February 4, 2003, at 03:46 PM, Jerzy Karczmarczuk wrote:


I would say that - unless I am dead wrong, the OO languages such as 
Smalltalk
do not dispatch on dynamic types of a value. The receiver is known, so 
its vir.
f. table (belonging to the receiver's class) is known as well, the 
dispatching
is based on the *message identifiers* independently of subsidiary 
arguments.

Yes, normally only the receiver and message identifier matters. In 
languages like Java, where the type of the other arguments is 
considered, this is handled statically.

For languages like Smalltalk, Objective-C, etc, all that you know at 
compile time is that the receiver is an object. You don't know what 
kind of object. Thus you cannot use a static dispatch style or vtables 
as you would in a language like C++. Even when the type is bounded, 
vtables are not enough because of categories and method packages 
that add methods to classes at run time.

Dispatch is done on the target (receiver) and selector (message 
identifier).

So if you consider an expression like:
	target_expr doSomething:arg_expr
then you should break that up into
	v = target_expr
	f = lookup_method(v, doSomething:)
	f(v, doSomething:, argexpr).

You dispatch on the dynamic type of the target (it's class) and on the 
dynamic state of its method tables. Note that you cannot assume that 
the receiver has a method that matches the selector!

Dynamic method lookup is a fairly complicated and expensive process, 
and it's a barrier to many optimizations. This can be mitigated by 
program analysis and specialization or similar techniques; dynamic 
dispatch and the surrounding problems are getting fairly well 
researched.

Languages with dynamic dispatch:
* Brad J Cox, Object oriented programming: an evolutionary approach, 
Addison-Wesley Longman Publishing Co., Inc., 1986
* Apple Computer, Inc., The Objective-C Programming Language, 2002.
  http://developer.apple.com/techpubs/macosx/Cocoa/ObjectiveC/index.html
* Pieter J. Schoenmaker, Supporting the Evolution of Software, Ph.D. 
thesis, Eindhoven University of Technology, July 1, 1999.

Some research:
* Zoran Budimlic, Ken Kennedy, and Jeff Piper, The cost of being 
object-oriented: A preliminary study, Scientific Computing 7(2), 1999
* David Detlefs and Ole Agesen, Inlining of Virtual Methods, Proc. of 
13th ECOOP
* A Diwan. Understanding and improving the performance of modern 
programming
languages. Ph.D. thesis, University of Massachusetts at Amherst. 
1997
* Peeter Laud, Analysis for Object Inlining in Java; 
http://citeseer.nj.nec.com/laud01analysis.html
* Ole Agesen and Jens Palsberg and Michael I. Schwartzbach, Type 
Inference of {SELF}: Analysis of Objects with Dynamic and Multiple 
Inheritance, Lecture Notes in Computer Science, 
http://citeseer.nj.nec.com/agesen93type.html

Only after that - perhaps - some reversions, message propagation 
depending on
the arg(s) value(s), etc. may take place, but all this is irrelevant...

Well,  self and the selector is usually an argument to the method, 
but otherwise I agree.

Regards,
John Hornkvist

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


Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
On 26-Jan-2003, John H?rnkvist [EMAIL PROTECTED] wrote:
 
 On Saturday, January 25, 2003, at 04:14 AM, Andrew J Bromage wrote:
 
 G'day all.
 
 On Fri, Jan 24, 2003 at 06:13:29PM -0500, Norman Ramsey wrote:
 
 In a fit of madness, I have agreed to deliver a 50-minute lecture
 on type classes to an audience of undergraduate students.  These
 students will have seen some simple typing rules for F2 and will
 have some exposure to Hindley-Milner type inference in the context
 of ML.
 
 Will they have had exposure to more traditional OO programming?  If
 so, it might be useful to note the difference between Haskell type
 classes and C++/Java/whatever classes, namely that Haskell decouples
 types and the interfaces that they support.  The advantage is that you
 can extend a type with a new interface at any point, not just when you
 define the type.
 
 While Java and C++ don't support it other object oriented languages do.

Some others do, some others don't.  And in fact it seems that most
mainstream OOP languages don't.  For example C#, Eiffel and Ada-95 don't,
if I recall correctly.  Sather does support it, but Sather is hardly
mainstream (the language is just about dead these days). 
GNU C++ used to support it, with the signature extension,
but doesn't anymore (support for that extension was dropped).
Of the vaguely mainstream OOP languages, I think only the dynamically-typed
ones support it.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
On 26-Jan-2003, Dean Herington [EMAIL PROTECTED] wrote:
 On Sun, 26 Jan 2003, Norman Ramsey wrote:
 
  A fact that I know but don't understand the implication of is that
  Haskell dispatches on the static type of a value, whereas OO languages
  dispatch on the dynamic type of a value.  But I suspect I'll leave
  that out :-)
 
 Perhaps I misunderstand, but I would suggest that fact is, if not 
 incorrect, at least oversimplified.

I agree.  The above characterization is highly misleading.  It would be
more accurate and informative to say that both Haskell and OO languages
dispatch on the dynamic type of a value.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
On 24-Jan-2003, Norman Ramsey [EMAIL PROTECTED] wrote:
 In a fit of madness, I have agreed to deliver a 50-minute lecture
 on type classes to an audience of undergraduate students.  These
 students will have seen some simple typing rules for F2 and will
 have some exposure to Hindley-Milner type inference in the context
 of ML.  I am soliciting advice about
   * Cool examples of type classes
   * Papers I could read to explain how to implement type classes,
 especially if I could show the `dictionary translation' which
 is then followed by ordinary Hindley-Milner type inference
   * Any other material on which I might base such a lecture

I quite like the idea of treating of type checking/inference as constraint
solving: ordinary Hindley-Milner style type inference involves
solving type unification constraints, and with type classes
you just generalize this to first-order predicate calculus
(type classes are predicates on types, and instance declarations
are clauses).

@InProceedings{demoen_et_al,
author =   {B. Demoen and M. {Garc\'{\i}a de la Banda} and
P.J. Stuckey},
title ={Type Constraint Solving for
Parametric and Ad-Hoc Polymorphism},
booktitle ={Proceedings of the 22nd
Australian Computer Science Conference},
pages ={217--228},
month =jan,
year = {1999},
location = {Auckland},
publisher ={Springer-Verlag},
isbn = {981-4021-54-7},
editor =   {J. Edwards},
}   

-- 
Fergus Henderson [EMAIL PROTECTED]  |  I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
On 26-Jan-2003, Norman Ramsey [EMAIL PROTECTED] wrote:
In a fit of madness, I have agreed to deliver a 50-minute lecture
on type classes to an audience of undergraduate students.  These
students will have seen some simple typing rules for F2 and will
have some exposure to Hindley-Milner type inference in the context
of ML.
   
   Will they have had exposure to more traditional OO programming?  If
   so, it might be useful to note the difference between Haskell type
   classes and C++/Java/whatever classes, namely that Haskell decouples
   types and the interfaces that they support.  The advantage is that you
   can extend a type with a new interface at any point, not just when you
   define the type.
 
 Hmm --- you are talking about the `instance' declarations, right?

Yes -- the fact that Haskell has separate instance declarations,
as opposed to making this information part of the `data' declaration.
In most OO languages inheritence relations need to be specified in the
type definition.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Lauri Alanko
On Mon, Jan 27, 2003 at 08:37:06PM +1100, Fergus Henderson wrote:
 I agree.  The above characterization is highly misleading.  It would be
 more accurate and informative to say that both Haskell and OO languages
 dispatch on the dynamic type of a value.

What is the dynamic type of a value in Haskell, apart from existentials
and Dynamic? Ordinary type class dispatch is all done based on the types of
variables, not their values. All the dispatching could even be done at
compile time by specializing everything...


Lauri Alanko
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Dylan Thurston
On Mon, Jan 27, 2003 at 12:25:52PM +0200, Lauri Alanko wrote:
 On Mon, Jan 27, 2003 at 08:37:06PM +1100, Fergus Henderson wrote:
  I agree.  The above characterization is highly misleading.  It would be
  more accurate and informative to say that both Haskell and OO languages
  dispatch on the dynamic type of a value.
 
 What is the dynamic type of a value in Haskell, apart from existentials
 and Dynamic? Ordinary type class dispatch is all done based on the types of
 variables, not their values. All the dispatching could even be done at
 compile time by specializing everything...

I don't think this is true, even without existential types.
Polymorphic recursion may involve building dictionaries at run time,
which certainly approaches dynamic dispatch.

(Polymorphic recursion is one of Chris Okasaki's favorite tricks.  It
involves definitions like

data Tree a = Leaf a | Node (Tree [a]) (Tree [a])

in which the variable 'a' is used recursively at a different type.)

Best,
Dylan Thurston



msg12142/pgp0.pgp
Description: PGP signature


Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Norman Ramsey
Now that I have made it abundantly clear that my understanding of type
classes is highly imperfect, perhaps I will repeat my plea:

  * Can you recommend any interesting, elementary examples?

  * Of all the many articles on the topic, which few might you
recommend for beginners?  Would Faxen's static semantics be a good
place to start?  Jones's `Typing Haskell in Haskell'?  One of Phil
Wadler's papers (which one)?

Thanks again for any help,


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



RE: seeking ideas for short lecture on type classes

2003-01-27 Thread Mark P Jones
Hi Norman,

| [looking for papers about type classes ...]
|   * Of all the many articles on the topic, which few might you
| recommend for beginners?

I wonder if my notes on Functional Programming with Overloading and
Higher-Order Polymorphism will be useful?  You can find them at:

  http://www.cse.ogi.edu/~mpj/pubs/springschool.html

They don't cover implementation aspects, but if your audience is more
interested in language/use than compilation issues, then I think they
might provide you with some reasonable starting material.

Hope this helps!
Mark

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



Re: seeking ideas for short lecture on type classes

2003-01-26 Thread Norman Ramsey
   In a fit of madness, I have agreed to deliver a 50-minute lecture
   on type classes to an audience of undergraduate students.  These
   students will have seen some simple typing rules for F2 and will
   have some exposure to Hindley-Milner type inference in the context
   of ML.
  
  Will they have had exposure to more traditional OO programming?  If
  so, it might be useful to note the difference between Haskell type
  classes and C++/Java/whatever classes, namely that Haskell decouples
  types and the interfaces that they support.  The advantage is that you
  can extend a type with a new interface at any point, not just when you
  define the type.

Hmm --- you are talking about the `instance' declarations, right?

A fact that I know but don't understand the implication of is that
Haskell dispatches on the static type of a value, whereas OO languages
dispatch on the dynamic type of a value.  But I suspect I'll leave
that out :-)


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



<    1   2   3   4   5   6   7   >