RE: separate class and type namespace

2006-01-31 Thread Simon Marlow
On 31 January 2006 03:42, John Meacham wrote:

> What do people think about seperating the class and type namespaces?
> one can always tell the difference syntactically which is meant, the
> only 
> thing keeping them in the same space in jhc is an artificial check to
> ensure you don't create some of the same name.
> 
> the only issue is in export/import lists if you wanted to allow
> import/export of the type independently of the class. however the
> proposed explicit namespace change to the import/export syntax would
> solve this too and it is unlikely to actually be a problem in
> practice. 

I've always liked the idea of saying 'class C' or 'type T' in
import/export lists.

It could be made backwards compatible: we allow types and classes to be
named the same, but in this case the export list has to use the new
syntax to disambiguate.  The idea would be to transition to the new
syntax eventually.

There's a choice about whether a newtype should be exported with
'newtype T' or 'data T', or either.

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


RE: The dreaded M-R

2006-01-31 Thread Simon Marlow
On 31 January 2006 00:53, Neil Mitchell wrote:

>> Second, a warning about "loss of sharing" may befuddle beginners (who
>> are usually not taught to write type signatures at the start).
> 
> Are standards documents the place for prescribing which warnings
> should be raised, and under what circumstances?

Not prescribing, no.  It would be a recommendation.  The Haskell 98
report already contains recommendations - see the section on pragmas,
for example, and I'm sure there are more examples.

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Mon, 2006-01-30 at 18:20 -0800, John Meacham wrote:
> so if I understand this proposal properly, it would mean the following
> 
> every single parameter type class whole parameter is of kind * 
> class Foo a where
> 
> automatically declares a data type defined as
> 
> data Foo = exists a . Foo a => Foo_ a   
> (where Foo_ is some internal, non user accessable name)
> 
> and an instance
> 
> instance Foo Foo where
> method (Foo_ x) = method x 
> ...
> 
> this all seems quite nice, I really like it, we can always determine
> whether a name is a class or type from context (I think the only reason
> the namespaces are combined is due to import/export lists)
> 
> the only issue is the autoboxing. we can't introduce an actual
> constructor because constructors are in a different namespace. so we
> would need to automatically turn anything of type Foo a => a into a Foo
> when it is used as such.

Is that really necessary (or desirable)?

As it was suggested in the thread on existential types it probably wants
to be made explicit when you throw away type information by putting
something behind an interface.

How about just making the conversion "Foo a => a -> Foo" explicit? And
of course the conversion is just the constructor Foo.

Duncan

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


RE: The dreaded M-R

2006-01-31 Thread Simon Marlow
On 30 January 2006 21:49, Andrew Pimlott wrote:

> On Mon, Jan 30, 2006 at 04:45:56PM -, Simon Marlow wrote:
>> Given the new evidence that it's actually rather hard to demonstrate
>> any performance loss in the absence of the M-R with GHC, I'm
>> attracted to the option of removing it in favour of a warning.
> 
> I caution against the hope that warnings will contribute to the
> solution, whichever side you're on.  This is a general argument: 
> Either the warning is on by default or off.  If off, it does no harm,
> but doesn't help much either.  If on, it either triggers only on code
> that is almost certainly wrong (or easily disambiguated), or it
> sometimes triggers on perfectly good code.  In the former case, it
> would be better to make it illegal (or require the disambiguation). 
> In the latter, nobody likes disabling warnings, so they'll grumble
> and change the code instead.
> 
> In the present case, people aren't (only) opposing the M-R out of
> principle, but because they actually use overloaded variable
> definitions and (at least sometimes) want to leave off the signature.
>
> So I don't see how one could claim, as on the wiki, the warning
> "wouldn't happen much".  I suspect it would happen, and annoy people,
> and defeat the reason that people want to remove the M-R.

The assertion that it "wouldn't happen much" is based on the observation
earlier in this thread that it was actually difficult to write some code
that illustrated the problem.

Nevertheless, I didn't mean to imply that the language would mandate a
warning, I'll change the wiki to make this more clear.

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


RE: ~ patterns

2006-01-31 Thread Simon Marlow
On 30 January 2006 18:20, Isaac Jones wrote:

> Can someone be sure to capture the pros, cons, and relationship to the
> !-patterns proposal as a ticket / wiki page?

I've been swayed by the arguments put forward by the ~-proponents, so
I'm not going to champion the removal of ~ any more.  

We must find *something* to throw away though! :-)

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Mon, 2006-01-30 at 18:20 -0800, John Meacham wrote:
> so if I understand this proposal properly, it would mean the following
> 
> every single parameter type class whole parameter is of kind * 
> class Foo a where
> 
> automatically declares a data type defined as

perhaps semi-automatically?

class Foo a where
  ...
  ...
  deriving data Foo

> data Foo = exists a . Foo a => Foo_ a   
> (where Foo_ is some internal, non user accessable name)
> 
> and an instance
> 
> instance Foo Foo where
> method (Foo_ x) = method x 
> ...
> 
> this all seems quite nice, I really like it, we can always determine
> whether a name is a class or type from context (I think the only reason
> the namespaces are combined is due to import/export lists)


Duncan

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


Re: The dreaded M-R

2006-01-31 Thread Tomasz Zielonka
[I have subscribed to the list today, so my mailbox doesn't contain the
post I should respond to (the one that started this thread). BTW, is
there a way to tell mailman to send me all previous postings?]

Concurrent Clean uses =: for "Constant Graph Definitions", which seem to
be related.

See Concurrent Clean V2.0 Language Report (Draft), section 3.6, Defining
Constants. This is page 24 in:

ftp://ftp.cs.kun.nl/pub/Clean/Clean20/doc/CleanRep2.0.pdf

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The dreaded M-R

2006-01-31 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> writes:

> Given the new evidence that it's actually rather hard to demonstrate any
> performance loss in the absence of the M-R with GHC, I'm attracted to
> the option of removing it in favour of a warning.

As another data point, today for the first time I received an error
(not a warning) from ghc about the M-R:

Ambiguous type variable `a' in the constraint:
  `Ord a' arising from use of `Data.Set.insert' at Pretty.hs:28:11-20
Possible cause: the monomorphism restriction applied to the following:
  addToSet :: a -> Data.Set.Set a -> Data.Set.Set a (bound at 
Pretty.hs:28:0)
Probable fix: give these definition(s) an explicit type signature
  or use -fno-monomorphism-restriction

So, without the M-R or a type signature, my code is OK.  The proposal
to accept this code but produce an optional warning is (I think)
better than the current error.

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


Re: Comment Syntax

2006-01-31 Thread Thomas Davie



The fact that -- is a reserved word while {- is not just highlights
farther the inconsistency in the language.


Your position implies one of the following:

1) You think that "{{" ought to be a legal operator.

2) You think that "-" ought not to be a legal operator.

3) You think that custom operators are a bad idea. (Hey, Bjarne
Stroustrup agrees with you!)

Which is it? Personally, I disagree with all three, but then again, I
don't see any inconsistency here.


4) I think that comments should start consistently with either a) a  
reserved word, or b) something involving a set character (or  
characters) not allowed in operators.  Maybe ever '{{' would be good  
for a single line comment.


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


Re: Comment Syntax

2006-01-31 Thread Georg Martius
On Tuesday 31 January 2006 12:31, Thomas Davie wrote:
> >> The fact that -- is a reserved word while {- is not just highlights
> >> farther the inconsistency in the language.
> >
> > Your position implies one of the following:
> >
> > 1) You think that "{{" ought to be a legal operator.
> >
> > 2) You think that "-" ought not to be a legal operator.
> >
> > 3) You think that custom operators are a bad idea. (Hey, Bjarne
> > Stroustrup agrees with you!)
> >
> > Which is it? Personally, I disagree with all three, but then again, I
> > don't see any inconsistency here.
>
> 4) I think that comments should start consistently with either a) a
> reserved word, or b) something involving a set character (or
> characters) not allowed in operators.  Maybe ever '{{' would be good
> for a single line comment.

a) a reserved word must be followed by space as well.
b) {{ is certainly a bad idea because of pairwise paretheses match
I feel no inconsitency with the current system and I think 
-- some comment
looks much better than
--some comment
anyway. My opinion: Your editor should support you. If it doesn't, than switch 
to a proper one our adapt the mode and share it with the other users.

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


Re: The dreaded M-R

2006-01-31 Thread Johannes Waldmann
Lennart Augustsson wrote:

> All that said, I think not being able to give a name to a context is
> a real weakness in Haskell.  It's one of the few things that cannot
> be named, and being able to do so would help refactoring and modularity.

definitely. Currently we have to simulate that by

class ( C1 , C2 , ... ) => Context
instance ( C1, C2 , .. ) => Context

(is it equivalent? I hope so)
but it is awkward to duplicate information like that.

best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: separate class and type namespace

2006-01-31 Thread Marcin 'Qrczak' Kowalczyk
"Simon Marlow" <[EMAIL PROTECTED]> writes:

> I've always liked the idea of saying 'class C' or 'type T' in
> import/export lists.

Type signatures too should be allowed in export lists.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: what's the goal of haskell-prime?

2006-01-31 Thread Wolfgang Jeltsch
Am Montag, 30. Januar 2006 19:33 schrieb Isaac Jones:
> [...]

> Have you looked at the Helium language / compiler?  It's a
> stripped-down version of Haskell for teaching.  Maybe that's what
> you're actually suggesting?  I think this is a great idea :)

I think the current Helium version causes too many problems because of the 
lack of type classes since type classes are normally used even with very 
fundamental things like numbers and value-to-string conversion.

> peace,
>
>   isaac

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Wolfgang Jeltsch
Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
> [...]

> I have often thought that it would be useful to have an existential
> corresponding to a class.

How would this work with multi-parameter classes, constructor classes, etc.? 
If you propose something that only works in conjunction with a special kind 
of classes I would hesitate to include such thing in a Haskell standard.

I think that it would often be nice to have Template Haskell standardized and 
implement features like autoboxing via some library using Template Haskell.  
This way, we would keep the actual language small but open the door for lots 
of useful extensions.  This principle of a small but powerful (extensible) 
language is used already a lot without Template Haskell, so why not use it 
also in conjunction with Template Haskell in cases like the autoboxing 
approach.

> [...]

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


Re: module system/namespaces: separate with/use, allow local "use"

2006-01-31 Thread Johannes Waldmann
Simon Marlow wrote:

>>> Perhaps 'import' should be allowed anywhere among definitions.

> [...] Against:
>  - tools that collect imports have to parse the whole file (eg. GHC's
>dependency analyser)
>  - can't easily see what is imported

only if we keep the idea that "import" both says *that* a module
is imported *and* brings it into scope at the same time.

Ada has "with" at the top (that would answer your objections)
and then allows local "use" for the scoping issues
(but you'd have to "with" any module that you want to "use").

I think the current "import .. qualified .. as .. hiding"
is trying to do too much at the same time.

best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: separate class and type namespace

2006-01-31 Thread John Meacham
On Tue, Jan 31, 2006 at 09:52:22AM -, Simon Marlow wrote:
> There's a choice about whether a newtype should be exported with
> 'newtype T' or 'data T', or either.

I would think it would be 'type T' since the category should identify
the namespace of what you are trying to export rather than what it is.

you certainly don't want to have to change import (data T) to import
(newtype T) when the implementation changes :)

the namespaces I can think of are class,type,value,kind,method,field

though, probably class,type,value and kind will be the only useful ones.
and 'value' could be the default if nothing is specified.

I like the idea of doing this too because it also gives a place to
attach other extensions to, like 'closed class Foo' if we decide we like
closed classes.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Bulat Ziganshin
Hello Duncan,

Monday, January 30, 2006, 9:02:48 PM, you wrote:

DC> class IStream s where
DC>   readBlock :: s -> IO Block

DC> data IStream = IStream {
DC>   istream_readBlock :: IO Block
DC> }

DC> instance IStream IStream where
DC>   readBlock s = istream_readBlock s

DC> abstractIStream :: IStream s => s -> IStream
DC> abstractIStream s = IStream { istream_readBlock = readBlock s }


how that is done in my lib:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool
.

data Handle = forall h . (Stream IO h) => Handle h

instance Stream IO Handle where
vClose(Handle h) = vCloseh
vIsEOF(Handle h) = vIsEOFh
.




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Wolfgang Jeltsch
Am Dienstag, 31. Januar 2006 03:20 schrieb John Meacham:
> [...]

> an alternative might be to just allow existential types in structures so
> we can have [exists a . Foo a => a], but that probably has its own can
> of worms...

But it sounds very reasonable to me, more reasonable than the autoboxing 
approach :-(.

> John

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Tue, 2006-01-31 at 13:59 +0100, Wolfgang Jeltsch wrote:
> Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
> > [...]
> 
> > I have often thought that it would be useful to have an existential
> > corresponding to a class.
> 
> How would this work with multi-parameter classes, constructor classes, etc.? 
> If you propose something that only works in conjunction with a special kind 
> of classes I would hesitate to include such thing in a Haskell standard.

As John Mecham said it'd be for single parameter type class with a
parameter of kind *.

But you're probably right that people should get more experience with
using this technique before giving special support in the language to
make it convenient.

As Bulat noted we can already use this construction:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool
.

data Handle = forall h . (Stream IO h) => Handle h

instance Stream IO Handle where
vClose(Handle h) = vCloseh
vIsEOF(Handle h) = vIsEOFh
.

But we have to give the name of the most general instance a different
name to the class which is rather inconvenient.

So perhaps we should start with allowing a class a data type to have the
same name and in a future standard think about making it easy to define
Bulat's Handle instance above with a short hand like:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool
.
  deriving data Stream


I have to say though that I am surprised that us Haskell folk are not
more interested in making it easy or even possible to have abstract
values accessed via interfaces. Classes make it easy and elegant to have
type based dispatch but for the few times when value based dispatch
really is necessary it's a pain. The fact that we've suffered with a
non-extensible abstract Handle type for so long is an example of this.

Duncan

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


Re: separate class and type namespace

2006-01-31 Thread Malcolm Wallace
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes:

> > I've always liked the idea of saying 'class C' or 'type T' in
> > import/export lists.
> 
> Type signatures too should be allowed in export lists.

Both ideas already noted at
http://haskell.galois.com/trac/haskell-prime/wiki/ModuleSystem

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


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Tue, 2006-01-31 at 13:28 +, Duncan Coutts wrote:
> On Tue, 2006-01-31 at 13:59 +0100, Wolfgang Jeltsch wrote:
> > Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
> > > [...]
> > 
> > > I have often thought that it would be useful to have an existential
> > > corresponding to a class.
> > 
> > How would this work with multi-parameter classes, constructor classes, 
> > etc.? 
> > If you propose something that only works in conjunction with a special kind 
> > of classes I would hesitate to include such thing in a Haskell standard.
> 
> As John Mecham said it'd be for single parameter type class with a
> parameter of kind *.
> 
> But you're probably right that people should get more experience with
> using this technique before giving special support in the language to
> make it convenient.
> 
> As Bulat noted we can already use this construction:
> 
> class (Monad m) => Stream m h | h->m where
> vClose :: h -> m ()
> vIsEOF :: h -> m Bool
> .
> 
> data Handle = forall h . (Stream IO h) => Handle h
> 
> instance Stream IO Handle where
> vClose(Handle h) = vCloseh
> vIsEOF(Handle h) = vIsEOFh
> .
> 
> But we have to give the name of the most general instance a different
> name to the class which is rather inconvenient.
> 
> So perhaps we should start with allowing a class a data type to have the
> same name and in a future standard think about making it easy to define
> Bulat's Handle instance above with a short hand like:
> 
> class (Monad m) => Stream m h | h->m where
> vClose :: h -> m ()
> vIsEOF :: h -> m Bool
> .
>   deriving data Stream

Actually this is unnecessary. All we need is:

class (Monad m) => Stream m h | h->m where
vClose :: h -> m ()
vIsEOF :: h -> m Bool

newtype Handle = exists s. Stream s => Handle s
  deriving Stream


So all we need is existentials and newtype-deriving.

Duncan

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


give equal rights to types and classes! :)

2006-01-31 Thread Bulat Ziganshin
Hello John,

Tuesday, January 31, 2006, 6:42:14 AM, you wrote:

JM> What do people think about seperating the class and type namespaces? one

i have exactly opposite idea - give the class and type names equal
rights :)  instead of writing

foo :: (Num a, Monad m) => a -> m ()

allow to write

foo :: Num -> Monad ()

and vice versa - instead of

bar :: Int -> [Int]

allow to write

bar :: (Int a, [] b) => a -> b a


That this gives?

1) significantly simplifies declarations using typeclasses. i
was seriously bitten by those huge declarations, and think that
simplification in this area will lead to much wider use of type
classes by the ordibary users (like me :) . ideally, i just don't need
to think whether a Foo is a class or type in most cases - both can be
used interchangeably (like interfaces and classes in Java)

2) this allows to refactor existing code without changing type
signatures. just for example - imagine that [] is now a typeclass
implementing only several basic operations, namely head/tail/(:)/null.
nevertheless, all those huge number of list-processing functions still
work because [] in their type signatures now means that
parameter/result belong to the some instance of this class. cool? i
think so :)

of course, that also need possibility to define pattern matching
(meaning of []/a:b) inside this class, but that's a different proposal
:)

two uses of the same class in one declaration should mean the same
type, as in:

reverse :: [a] -> [a]

what is equivalent to

reverse :: ([] c) => c a -> c a

Of course, refactoring of [] is just amazing example. what i basically
mean - when program grows and some T becomes an interface instead of
type, there should be no need to change all the T usages - they will
continue to work, work and work. The only exception will be type
signatures, where T is used ywo times or more and different T's usages
can mean different types. in this case, we need to switch to expanded
signature, what nevertheless should work even if T is still just a
type:

cvt :: (T a, T b) => a->b


JM> this would allow things like one to have a class and a data type holding
JM> an arbitrary member of said class to have the same name

_may be_, my proposal can even solve your problem






-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: separate class and type namespace

2006-01-31 Thread Johannes Waldmann

> Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes:
>> Type signatures too should be allowed in export lists.

I'm all for type signatures, but I am slightly worried in that this
leads to duplication of information (giving the signature both in the
export list and at the place of definition). What about having
"private/public" access modifiers at the points of definition instead,
and removing export lists altogether?

If we know beforehand what functions of what names and types
a module *must* export (by design), in other words, if the intention
is that the compiler checks whether the implementation matches the
exported specification, then we should write an interface
(i. e. unary type class) and declare an instance. Then the module
should export nothing but the instance. The problem with this is that an
interface says something about a type while a Haskell module might
export many things (functions, types) at the same time. So there is in
fact no formal "interface" concept for modules, leading to mis-use of
qualified imports for that (import qualified My_Bar as Bar, when I know
that My_Bar behaves "as a Bar"). So a Haskell module is more like a Java
package  than a Java class. On the other hand, it is recommended
practice to define only one data type per module, isn't it?

Respectfully submitted,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


Re: give equal rights to types and classes! :)

2006-01-31 Thread Johannes Waldmann
Bulat Ziganshin wrote:

> instead of writing 
> foo :: (Num a, Monad m) => a -> m ()
> allow to write
> foo :: Num -> Monad ()

as has been noted, that would be special treatment
for unary type classes with argument of kind *.

Also, *if* we want such a shorthand, it is not clear whether we want
existential or forall typing per default. Referring to your example,
the "foo" function must be able to return a value in *each* monad
that the caller specifies at the call site, while we were discussing
functions that make their own choice of returning *some* monad instance.

Best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

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


FW: mr

2006-01-31 Thread Simon Peyton-Jones
I thought you might be interested in this brief exchange between John
and myself.  (I was starting from Simon Marlow's idea of pattern binding
=> monomorphic.)

Simon

-Original Message-
From: John Hughes [mailto:[EMAIL PROTECTED] 
Sent: 31 January 2006 14:40
To: Simon Peyton-Jones
Subject: Re: mr

Simon Peyton-Jones wrote:

>John
>
>How about this:
>
>A binding for a pattern or variable, that lacks a type signature, is
>treated as follows:
>
>* At top level: polymorphic, but illegal if overloaded
>* Nested: monomorphic
>
>The reason for the difference is that at top level there's no context,
>so forcing monomorphic is bad.  Whereas for nested bindings it seems
>like the right thing to force a signature, which will either resolve
the
>overloading or declare it.
>
>Simon
>  
>
I can see the attraction--it seems to "do the right thing" in each case.

But aesthetically,
I think it's ghastly. Now to understand a variable definition, one need 
not look (through
the entire module) to see if it has a type signature, but also look to 
see whether it is top
level or not! Refactoring that moves definitions in and out of where 
blocks (pretty
common!) would also risk introducing type errors. That would be a trap 
for the unwary
(and we were all unwary once upon a time).

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


Re: The dreaded M-R

2006-01-31 Thread John Hughes



   "Simon Marlow" <[EMAIL PROTECTED]> writes:


Given the new evidence that it's actually rather hard to demonstrate any
performance loss in the absence of the M-R with GHC, I'm attracted to
the option of removing it in favour of a warning.
   



   As another data point, today for the first time I received an error
   (not a warning) from ghc about the M-R:

   Ambiguous type variable `a' in the constraint:
   `Ord a' arising from use of `Data.Set.insert' at Pretty.hs:28:11-20
   Possible cause: the monomorphism restriction applied to the following:
   addToSet :: a -> Data.Set.Set a -> Data.Set.Set a (bound at
   Pretty.hs:28:0)
   Probable fix: give these definition(s) an explicit type signature
   or use -fno-monomorphism-restriction

   So, without the M-R or a type signature, my code is OK. The proposal
   to accept this code but produce an optional warning is (I think)
   better than the current error.

   Regards,
   Malcolm


Well, is it OK? From the type-checker's point of view, yes, But have you lost
sharing? Have you introduced a space leak, because a seq on one of the 
occurrences
of your variable only forces one instance? Those are the dangers of following 
the
advice to put a type signature in.

John

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


Re: The dreaded M-R

2006-01-31 Thread Malcolm Wallace
John Hughes <[EMAIL PROTECTED]> writes:

> Ambiguous type variable `a' in the constraint:
>   `Ord a' arising from use of `Data.Set.insert' at Pretty.hs:28:11-20
> Possible cause: the monomorphism restriction applied to the following:
>   addToSet :: a -> Data.Set.Set a -> Data.Set.Set a
> Probable fix: give these definition(s) an explicit type signature
>   or use -fno-monomorphism-restriction
> 
> Well, is it OK? From the type-checker's point of view, yes, But have you
> lost sharing?

Yes, I have lost sharing, but then again, sharing is impossible here
anyway.  In fact, the monomorphism restriction wanted to force sharing,
but the types indicated it was not possible, hence the error.  :-)

What the M-R was complaining about, is my having eta-reduced a
definition into completely point-free style.

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


Re: separate class and type namespace

2006-01-31 Thread Aaron Denney
On 2006-01-31, Johannes Waldmann <[EMAIL PROTECTED]> wrote:
>
>> Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes:
>>> Type signatures too should be allowed in export lists.
>
> I'm all for type signatures, but I am slightly worried in that this
> leads to duplication of information (giving the signature both in the
> export list and at the place of definition). What about having
> "private/public" access modifiers at the points of definition instead,
> and removing export lists altogether?

Reexporting from sub-modules.

-- 
Aaron Denney
-><-

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


Re: The dreaded M-R

2006-01-31 Thread Andrew Pimlott
On Tue, Jan 31, 2006 at 10:17:57AM -, Simon Marlow wrote:
> On 30 January 2006 21:49, Andrew Pimlott wrote:
> > In the present case, people aren't (only) opposing the M-R out of
> > principle, but because they actually use overloaded variable
> > definitions and (at least sometimes) want to leave off the signature.
> >
> > So I don't see how one could claim, as on the wiki, the warning
> > "wouldn't happen much".  I suspect it would happen, and annoy people,
> > and defeat the reason that people want to remove the M-R.
> 
> The assertion that it "wouldn't happen much" is based on the observation
> earlier in this thread that it was actually difficult to write some code
> that illustrated the problem.

This indicates that the warning "wouldn't happen much" _when you want
sharing_.  But it would happen all the time when you don't want sharing,
eg. in the case Malcolm Wallace just posted.

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


Re: ~ patterns

2006-01-31 Thread Taral
On 1/31/06, Simon Marlow <[EMAIL PROTECTED]> wrote:
> I've been swayed by the arguments put forward by the ~-proponents, so
> I'm not going to champion the removal of ~ any more.
>
> We must find *something* to throw away though! :-)

I still like the idea of splitting Haskell' into Haskell'-core and
Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.

--
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: separate class and type namespace

2006-01-31 Thread Cale Gibbard
> On the other hand, it is recommended
> practice to define only one data type per module, isn't it?

Only by very few people as far as I know. I know that Henning
Thielemann advocates this, but it seems like a rather arbitrary
restriction to me. I find it quite common to define several data types
in a single module, so long as they're sufficiently related. Depending
on how they are used, I may or may not export any one of them.

Have a look at Basics.lhs in Haskore, then imagine separating that
such that every one of those data types was in its own module. You'd
end up with a lot of modules which only had one data type in them and
nothing else. I think it's just better to use your own picture of how
the project fits together to decide where to put things. Unless you're
explicitly using modules for hiding data constructors, it doesn't seem
necessary to structure your modules around your types.

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


Re: The dreaded M-R

2006-01-31 Thread Ben Rudiak-Gould

Josef Svenningsson wrote:

There are many evaluation strategies one can use to implement Haskell.
The problem with the M-R is that it is a concern only in *some* of these 
evaluation strategies, most notably lazy evaluation.


True, but it's a concern in any evaluation strategy that tries to avoid
multiple evaluation of let-bound expressions, which includes lazy,
optimistic, and eager evaluation. A strict dialect of ML with type classes
would face the same problems.


If you read the motivation section which defines the M-R [...] the report
suddenly starts to talk about how many times a certain a certain 
expression is evaluated. But nowhere in the report is it defined how 
expressions should be evaluated. This makes the M-R truly butt-ugly!


I agree, but you don't have to specify lazy evaluation in order to justify
the M-R. Some sort of nondeterministic graph reduction semantics would be
good enough.

-- Ben

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


Re: The dreaded M-R

2006-01-31 Thread Ben Rudiak-Gould

John Meacham wrote:

interestingly enough, the monomorphism restriction in jhc actually
should apply to all polymorphic values, independently of the type class
system.

x :: a 
x = x 


will transform into something that takes a type parameter and is hence
not shared.


Interesting. I'd been wondering how you dealt with this case, and now it 
turns out that you don't. :-)



I doubt this will cause a problem in practice since there
arn't really any useful values of type forall a . a other than bottom.


It could become an issue with something like

  churchNumerals :: [(a -> a) -> (a -> a)]
  churchNumerals = ...

Maybe you could use a worker-wrapper transformation.

  churchNumerals' :: [(T -> T) -> (T -> T)]
  churchNumerals' = ...

  churchNumerals :: [(a -> a) -> (a -> a)]
  churchNumerals = /\ a . unsafeCoerce churchNumerals'

The unsafeCoerce is scary, but it feels right to me. There is something 
genuinely unsavory about this kind of sharing, in Haskell or any other ML 
dialect. At least here it's out in the open.


-- Ben

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


Re: ~ patterns

2006-01-31 Thread Ben Rudiak-Gould

John Hughes wrote:

Quick, when I write do (x,y)<-e... is that pair matched strictly, like
case, or lazily, like let? If strictly, then why? There's no choice to be
made here, so why not wait until x or y is used before matching?


The choice of whether to invoke fail can't be postponed. Admittedly fail 
will never be called in this case, but I think legislating special behavior 
for such cases would be a bad idea. What would (x,[]) <- e mean?



If only pattern matching was *always*
strict, unless a ~ appeared, then the language would be more regular and
easier to learn.


But then (let 1=2 in "Whee!") wouldn't work properly any more. :-)

-- Ben

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


RE: ~ patterns

2006-01-31 Thread Simon Marlow
On 30 January 2006 12:32, John Hughes wrote:

> I don't really agree that ~ adds complexity to the language design,
> given that we need
> SOME mechanism for lazy pattern matching. If you write
> a denotational semantics of pattern matching, then ~ fits in
> naturally. It has a simple,
> compositional semantics. Where I see complexity is that a pattern
> means different
> things in a let or in a case, so I have to remember, for each
> construct, whether it's
> a strict-matching or lazy-matching construct. Quick, when I write do
> (x,y)<-e...
> is that pair matched strictly, like case, or lazily, like let? If
> strictly, then why? There's
> no choice to be made here, so why not wait until x or y is used before
> matching? I expect
> you know the answer to this question off-hand, but it's an obstacle to
> learning the
> language--I'll bet there are many quite experienced Haskell
> programmers who are
> uncertain. If only pattern matching was *always* strict, unless a ~
> appeared, then the
> language would be more regular and easier to learn.

For what it's worth, I agree with this point.  I'd be quite happy for
pattern matching to be strict by default in let and where.

I can imagine it might still be confusing to some, though, because

   let x = fac 99

does not evaluate 'fac 99', but

   let (x,y) = quotRem a b

does evaluate 'quotRem a b'.  Still, I suppose it's no more confusing
than the current situation.

If pattern matching in where was strict, I imagine I'd use ~ a lot more.
A common practice is to throw a bunch of bindings into a where clause,
with no regard for whether they get evaluated or not - variable bindings
and pattern bindings alike.  If the pattern bindings are strict, I have
to add ~ to each one to get the same effect.

On the other hand, if pattern bindings were strict by default, I bet
there would be a lot fewer accidental space leaks.

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


Re: ~ patterns

2006-01-31 Thread John Meacham
On Tue, Jan 31, 2006 at 12:26:16PM -0600, Taral wrote:
> On 1/31/06, Simon Marlow <[EMAIL PROTECTED]> wrote:
> > I've been swayed by the arguments put forward by the ~-proponents, so
> > I'm not going to champion the removal of ~ any more.
> >
> > We must find *something* to throw away though! :-)
> 
> I still like the idea of splitting Haskell' into Haskell'-core and
> Haskell'-lazy, and moving ~ and ! patterns into Haskell'-lazy.

I'd flip the names though. since lazy programers are the ones that will
create implementations that only conform to the lesser standard :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: ~ patterns

2006-01-31 Thread Patryk Zadarnowski

On 31/01/2006, at 9:31 PM, Simon Marlow wrote:


We must find *something* to throw away though! :-)


One small issue that I'd love to see thrown away is the special  
handling the the unary "-"
operator in Haskell 98. It's been described as "embarrassing",  
"ugly", and even "inconvenient"
I, for one, find myself creating sections of the form `+ (-x)` all  
the time, and it feels wrong.


The proposal would be to remove the unary "-" altogether, and,  
instead, extend the lexical
syntax of numeric constant to allow "+" and "-" prefix. Further, we  
would need to extend

the prelude with an additional definition:

negate :: Num a -> Num a
negate x = 0 - x

Pros:

1. Removes an embarrassing special case from the grammar.
2. Makes the section `- x` work as expected.
3. Expressions such as "-1" would not require paranthesizing.
4. Expressions such as "-1" would be permitted in k-patterns
even if n+k patterns end up being thrown out.
5. You can say "negate $ 1 + 2" if you don't like parentheses.
6. The precedent of making an operator symbol behave differently when
not separated from its argument by a space has already been made by
the "." operator.

Cons:

1. Expressions of the form "-x" (where "x" is not a constant) need to  
be rewritten
as "negate x" (which, to me, looks much cleaner anyway,  
especially as, more

often than not, "x" ends up being a complex expression anyway!

2. Possible confusion to the beginners (can write "-1" but cannot  
write "-x".)
However, I think that the strange behaviour of sections and the  
need for
parentheses around "-1" is already confusing enough to  
beginners, and
therefore this chance would actually make Haskell *easier* to  
learn, not

harder. "negate x" looks so much more like ordinary Haskell code!

What do people think?

- Pat.

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


Re: ~ patterns

2006-01-31 Thread John Meacham
On Wed, Feb 01, 2006 at 11:32:28AM +1100, Patryk Zadarnowski wrote:
> On 31/01/2006, at 9:31 PM, Simon Marlow wrote:
> 
> >We must find *something* to throw away though! :-)
> 
> One small issue that I'd love to see thrown away is the special  
> handling the the unary "-"
> operator in Haskell 98. It's been described as "embarrassing",  
> "ugly", and even "inconvenient"
> I, for one, find myself creating sections of the form `+ (-x)` all  
> the time, and it feels wrong.
> What do people think?

yeah, I really want to see this change too. I think it would be a whole
lot nicer. plus, a syntax highlighting editor would be able to determine
the difference between - used as an operator and - used as part of a
number.
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: ~ patterns

2006-01-31 Thread isaac jones
On Tue, 2006-01-31 at 16:47 -0800, John Meacham wrote:
> On Wed, Feb 01, 2006 at 11:32:28AM +1100, Patryk Zadarnowski wrote:
> > On 31/01/2006, at 9:31 PM, Simon Marlow wrote:
> > 
> > >We must find *something* to throw away though! :-)
> > 
> > One small issue that I'd love to see thrown away is the special  
> > handling the the unary "-"
> > operator in Haskell 98. It's been described as "embarrassing",  
> > "ugly", and even "inconvenient"
> > I, for one, find myself creating sections of the form `+ (-x)` all  
> > the time, and it feels wrong.
> > What do people think?
> 
> yeah, I really want to see this change too. I think it would be a whole
> lot nicer. plus, a syntax highlighting editor would be able to determine
> the difference between - used as an operator and - used as part of a
> number.

Would one of you make sure that these pros & cons are reflected in this
ticket or the linked wiki page:
http://hackage.haskell.org/trac/haskell-prime/ticket/50

peace,

  isaac

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


Re: ~ patterns

2006-01-31 Thread John Meacham
On Tue, Jan 31, 2006 at 11:05:37PM -, Simon Marlow wrote:
> On the other hand, if pattern bindings were strict by default, I bet
> there would be a lot fewer accidental space leaks.

I don't think this is true. I think there would just be a whole lot of a
different type of space leak. Lazy by default is more in the spirit of
haskell. case, function, and monadic binding matching is only strict out
of necessity since they actually need to scrutinize the values and that
makes perfect sense. if anything were to change, I'd make lambda
patterns lazy. (though, I don't feel particularly strongly about that,
since a case could be made for them being just a degenerate function
binding with only one alternative)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime