Re: [Haskell] question about a failure to generalize

2007-09-16 Thread Tom Pledger

Quoting Stefan O'Rear <[EMAIL PROTECTED]>:


On Mon, Sep 17, 2007 at 04:15:10PM +1200, Tom Pledger wrote:

Norman Ramsey wrote:
 :
 | This code fails to compile because the compiler is willing to
 | use 'fold' at only one type (CmmExpr as it happens)
 :

When it failed to compile, was

fold = foldRegsUsed

a top-level declaration in the module, rather than local to foldRegsUsed?

If so, try working around the monomorphism restriction by changing from a
pattern binding to a function binding.

fold f = foldRegsUsed f


The monomorphism restriction is not affected by top-level-or-not, see
sections 4.5.1 and 4.5.5 in the Haskell 98 Language and Libraries
Report.

Stefan



Aargh!  Sorry, I'm having a Bad Details Day.  3 in 1 message:

  - Overlooking the "to make the code work, I had to expand 'fold'
into 'foldRegsUsed' everywhere it appears" part in the original
question,

  - Chopping a letter out of Norman's email address, and

  - Mixing up the MR with other issues, possibly something from the
binding groups section of Typing Haskell In Haskell.

The one saving grace is that I tested my suggestion before posting,  
and it worked.  :-)


- Tom


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


Re: [Haskell] question about a failure to generalize

2007-09-16 Thread Stefan O'Rear
On Mon, Sep 17, 2007 at 04:15:10PM +1200, Tom Pledger wrote:
> Norman Ramsey wrote:
>  :
>  | This code fails to compile because the compiler is willing to
>  | use 'fold' at only one type (CmmExpr as it happens)
>  :
>
> When it failed to compile, was
>
> fold = foldRegsUsed
>
> a top-level declaration in the module, rather than local to foldRegsUsed?
>
> If so, try working around the monomorphism restriction by changing from a 
> pattern binding to a function binding.
>
> fold f = foldRegsUsed f

The monomorphism restriction is not affected by top-level-or-not, see
sections 4.5.1 and 4.5.5 in the Haskell 98 Language and Libraries
Report.

Stefan


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


[Haskell] question about a failure to generalize

2007-09-16 Thread Tom Pledger

Norman Ramsey wrote:
 :
 | This code fails to compile because the compiler is willing to
 | use 'fold' at only one type (CmmExpr as it happens)
 :

When it failed to compile, was

fold = foldRegsUsed

a top-level declaration in the module, rather than local to foldRegsUsed?

If so, try working around the monomorphism restriction by changing  
from a pattern binding to a function binding.


fold f = foldRegsUsed f

Regards,
Tom


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


Re: [Haskell] Swapping parameters and type classes

2007-09-16 Thread Stefan O'Rear
On Sun, Sep 16, 2007 at 10:45:39PM +0200, Bas van Dijk wrote:
> On 9/16/07, Mads Lindstrøm <[EMAIL PROTECTED]> wrote:
> > But what if I want to "apply" the 'b' ? How do I do that ?
> 
> The following uses type families (functions) and compiles under GHC HEAD:
> 
> {-# OPTIONS_GHC -XTypeFamilies -XEmptyDataDecls -XTypeSynonymInstances #-}

Eek!

That should be:

{-# LANGUAGE TypeFamilies, EmptyDataDecls, TypeSynonymInstances #-}

Modulo the fact that only GHC support type families at the moment, the
latter will be portable...

(Ian/Simon: I've seen this several times now.  Maybe there should be a
warning for -X in OPTIONS?  Is that even feasable?)

Stefan


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


Re: [Haskell] Swapping parameters and type classes

2007-09-16 Thread Bas van Dijk
On 9/16/07, Bas van Dijk <[EMAIL PROTECTED]> wrote:
> The following uses type families (functions) and compiles under GHC HEAD:
> ...

Oops this is not correct! Its getting late... oh well

Bas
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Swapping parameters and type classes

2007-09-16 Thread Bas van Dijk
On 9/16/07, Mads Lindstrøm <[EMAIL PROTECTED]> wrote:
> But what if I want to "apply" the 'b' ? How do I do that ?

The following uses type families (functions) and compiles under GHC HEAD:

{-# OPTIONS_GHC -XTypeFamilies -XEmptyDataDecls -XTypeSynonymInstances #-}

data Foo a b

class Bar (x :: * -> *)

instance Bar (Foo a)

type family BarB a b :: * -> *
type instance BarB a b = Foo b

instance Bar (BarB a b)


regards,

Bas van Dijk
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Swapping parameters and type classes

2007-09-16 Thread Brent Yorgey
On 9/16/07, Mads Lindstrøm <[EMAIL PROTECTED]> wrote:
>
> Hi all
>
> If I have this type:
>
>   data Foo a b = ...
>
> and this class
>
>   class Bar (x :: * -> *) where ...
>
> I can imagine two ways to make Foo an instance of Bar. Either I must
> "apply" the 'a' or the 'b' in (Foo a b). Otherwise it will not have the
> right kind. To "apply" the 'a' I can do:
>
>   instance Bar (Foo a) where ...
>
> But what if I want to "apply" the 'b' ? How do I do that ?


One easy way would be to create a newtype with the type parameters swapped:

  newtype Oof b a = Oof (Foo a b)
  instance Bar (Oof b) where ...

Of course, if you want to partially apply the second parameter of a
function, you use 'flip'.  I thought for a while about whether there's some
sort of typeclass hackery which is directly parallel to the use of 'flip',
but couldn't come up with anything.  Anyone?

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


Re: [Haskell] HaL2: Meeting Haskell in Leipzig 2, videos and presentations online

2007-09-16 Thread Wolfgang Jeltsch
Am Sonntag, 16. September 2007 14:22 schrieb klaus meier:
> Hello haskell friends!
>
> The Videos and presentations of the talks given at HaL2 are now online:

> […]

> 2 Wolfgang Jeltsch (TU Cottbus) talks about "Grapefruit, a Haskell-
> library for the declarative description of graphic user interfaces"

I’d like to add that this video doesn’t cover the complete talk but only the 
first five minutes. :-(  Alf, could you please make sure that this gets 
corrected? Thanks a lot!

> […]

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Records

2007-09-16 Thread Barney Hilken
Now that I have a version of ghc with type classes, I have had a go  
at implementing records based on the ideas I mentioned on this list a  
few months ago. The code of my first attempt is available at http:// 
homepage.ntlworld.com/b.hilken/files/Records.hs


I am releasing this to get feedback. I think Haskell needs a records  
system of this kind of generality, and this code at least allows you  
to play around.


From the comment section of the file:
---

Record construction:

EmptyRecis the empty record.
N =: x  is the record with one field labelled N  
carrying data x.
t +: u  is the union of records t and u. Any overlap  
of labels gives a static error.


Record destruction:

t .: N  is the value of field N in record t. A lack  
of field N gives a static error.
t -: N  is record t with field N deleted. A lack of  
field N gives a static error.


Record update:

t |: u  is the record with fields from u where it  
has them, t otherwise. If u has
any fields not in t, or of different types  
from t, there is a static error.

Note that the result has the same type as t.

All these records have types:

EmptyRecis the type of the empty record.
N :=: a is the type of a record with one field  
labelled N carrying data of type a.
r :+: s is the union of record types r and s. Any  
overlap of labels gives a static error.
r :.: N is the type of field N in a record of type  
r. A lack of field N gives a static error.
r :-: N is record type r with field N deleted. A  
lack of field N gives a static error.


Finally some classes to govern the polymorphism:

r `Contains` N  means that r is a record type with a  
field labelled N.
r `Disjoint` s  means that r and s are record types with  
no fields in common.
r `Subrecord` s means that r and s are record types, and  
every field of r also occurs in s (with the same type).


The types of the basic operators are as follows:

(=:) :: n -> a -> n :=: a
(+:) :: r `Disjoint` s => r -> s -> r :+: s
(.:) :: r `Contains` n => r -> n -> r :.: n
(-:) :: r `Contains` n => r -> n -> r :-: n
(|:) :: r `Subrecord` s => s -> r -> s

--

Note that these records are a lot more expressive than the Hugs  
system, as you can not only extend records by adding fields, but also  
take unions of arbitrary (disjoint) records.


Record update is designed for functions with lots of named optional  
arguments. If you define


f opts = ... options.:Optj ...
where
options = (Opt1 =: val1 +: ... +: Optn =: valn) |: opts

then the user can write (for example):

f (Optk =: u +: Optl =: v)

to set just two of the options, leaving the rest as default. This  
also cannot be done in the Hugs system.



The main disadvantage of the current implementation is that you have  
to tell the compiler in which order to store the fields, by defining  
one of the following:


   type instance NameCmp N M = NameLT
   type instance NameCmp N N = NameEQ
   type instance NameCmp N M = NameGT

for each pair of labels N & M in such a way as to give a linear order  
on labels. You need n^2 definitions, where n is the number of labels.  
I would do this in Template Haskell, but it won't yet allow you to  
declare type instances. Maybe some compiler support?


Error messages tend to be cryptic. They mostly complain of missing  
instances, and can run to several pages. There is really no way to  
improve this without building it all in to the compiler!



All comments gratefully received, including suggestions on syntax,  
choice of operators, implementation, explanation, etc.



Barney.


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


[Haskell] Swapping parameters and type classes

2007-09-16 Thread Mads Lindstrøm
Hi all

If I have this type:

  data Foo a b = ...

and this class

  class Bar (x :: * -> *) where ...

I can imagine two ways to make Foo an instance of Bar. Either I must
"apply" the 'a' or the 'b' in (Foo a b). Otherwise it will not have the
right kind. To "apply" the 'a' I can do:

  instance Bar (Foo a) where ...

But what if I want to "apply" the 'b' ? How do I do that ?


Greetings,

Mads Lindstrøm


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


[Haskell] HaL2: Meeting Haskell in Leipzig 2, videos and presentations online

2007-09-16 Thread klaus meier

Hello haskell friends!

The Videos and presentations of the talks given at HaL2 are now online:

http://iba-cg.de/haskell.html

Meeting HaL2, Leipzig Germany 10th of July

Talks: (first in english, remaining in german)
1 Johan Jeuring (Uni Uetrecht) talks about "Generic Programming in  
Haskell"
2 Wolfgang Jeltsch (TU Cottbus) talks about "Grapefruit, a Haskell- 
library for the declarative description of graphic user interfaces"
3 Henning Thielemann (Uni Halle) talks about "Calculation of sound in  
Haskell"
4 Leif Frenzel (Karlsruhe) introduced Cohatoe: "Writing eclipse- 
plugins in haskell"


We hope to see you on the next HaL meeting in the first quarter of 2008.

Greetings, Alf Richter
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell