Re: Comment Syntax

2006-02-11 Thread Wolfgang Jeltsch
Am Freitag, 3. Februar 2006 01:39 schrieb John Meacham:
> On Thu, Feb 02, 2006 at 06:19:43PM -0600, Taral wrote:
> > Got a unicode-compliant compiler?
>
> sure do :)
>
> but it currently doesn't recognize any unicode characters as possible
> operators. which it should, but I am just not sure how to specify that
> yet until some sort of standard develops.

Doesn't the Haskell Report tell which characters can be used in operators?

> [...]

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


Re: Comment Syntax

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 01:43:15PM -, Simon Marlow wrote:
> GHC treats the Unicode categories Sm, Sc, Sk and So as symbols, FWIW.
> These are the same characters for which Data.Char.isSymbol returns True.

cool. I will try to make jhc do the same thing.

> How do you implement the Data.Char predicates in jhc, BTW?

for now just via the following ffi call:
(though the plain 'module Char' just uses the report definitions for now)

> newtype CType = CType Int
>
> -- | Get a ctype other than one of the defaults.
>
> ctype :: String -> IO CType
> ctype s = withCString s >>= c_wctype
>
> t_alnum, t_alpha, t_blank, t_cntrl,
>  t_digit, t_graph, t_lower, t_print,
>  t_punct, t_space, t_upper, t_xdigit, t_none :: CType
>
> t_alnum = unsafePerformIO (ctype "alnum")
> t_alpha = unsafePerformIO (ctype "alpha")
> t_blank = unsafePerformIO (ctype "blank")
> t_cntrl = unsafePerformIO (ctype "cntrl")
> t_digit = unsafePerformIO (ctype "digit")
> t_graph = unsafePerformIO (ctype "graph")
> t_lower = unsafePerformIO (ctype "lower")
> t_print = unsafePerformIO (ctype "print")
> t_punct = unsafePerformIO (ctype "punct")
> t_space = unsafePerformIO (ctype "space")
> t_upper = unsafePerformIO (ctype "upper")
> t_xdigit = unsafePerformIO (ctype "xdigit")
> t_none = CType 0
>
> foreign import ccall "wctype.h iswctype" c_iswctype :: Char -> CType -> IO Int
> foreign import ccall "wctype.h wctype" c_wctype :: CString -> IO CType


John


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


RE: Comment Syntax

2006-02-03 Thread Simon Marlow
On 03 February 2006 00:40, John Meacham wrote:

> On Thu, Feb 02, 2006 at 06:19:43PM -0600, Taral wrote:
>> Got a unicode-compliant compiler?
> 
> sure do :)
> 
> but it currently doesn't recognize any unicode characters as possible
> operators. which it should, but I am just not sure how to specify that
> yet until some sort of standard develops. Once there are more unicode
> compliant compilers out there something will evolve probably. Right
> now I am thinking of being able to add a PRAGMA to force some
> characters to be interpreted as operators just so that they can start
> being used now, even though there isn't a standard set you can count
> on yet. 

GHC treats the Unicode categories Sm, Sc, Sk and So as symbols, FWIW.
These are the same characters for which Data.Char.isSymbol returns True.

How do you implement the Data.Char predicates in jhc, BTW?

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


Re: Comment Syntax

2006-02-02 Thread John Meacham
On Thu, Feb 02, 2006 at 06:19:43PM -0600, Taral wrote:
> Got a unicode-compliant compiler?

sure do :)

but it currently doesn't recognize any unicode characters as possible
operators. which it should, but I am just not sure how to specify that
yet until some sort of standard develops. Once there are more unicode
compliant compilers out there something will evolve probably. Right now
I am thinking of being able to add a PRAGMA to force some characters to
be interpreted as operators just so that they can start being used now,
even though there isn't a standard set you can count on yet.

John

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


Re: Comment Syntax

2006-02-02 Thread Taral
On 2/2/06, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> Am Montag, 30. Januar 2006 17:24 schrieb Taral:
> > On 1/30/06, Thomas Davie <[EMAIL PROTECTED]> wrote:
> > > It gives you regexp and nothing more - this makes it a pain in the
> > > arse to input every possible character that is/isn't allowed.
> >
> > Steal it from places (vim):
> >
> > syn match   hsLineComment  "---*\([^-!#$%&\*\+./<=>[EMAIL 
> > PROTECTED]|~].*\)\?$"
>
> What about Unicode?

Got a unicode-compliant compiler?

--
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: Comment Syntax

2006-02-02 Thread Wolfgang Jeltsch
Am Montag, 30. Januar 2006 17:24 schrieb Taral:
> On 1/30/06, Thomas Davie <[EMAIL PROTECTED]> wrote:
> > It gives you regexp and nothing more - this makes it a pain in the
> > arse to input every possible character that is/isn't allowed.
>
> Steal it from places (vim):
>
> syn match   hsLineComment  "---*\([^-!#$%&\*\+./<=>[EMAIL 
> PROTECTED]|~].*\)\?$"

What about Unicode?

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


Re: Comment Syntax

2006-02-02 Thread Manuel M T Chakravarty
Josef Svenningsson:
> I'm in favour of changing the comment syntax.
> 
> On 2/2/06, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> I am against such a change.  The change would break existing
> software
> (eg, Yampa) and secondly I don't buy the "main sources of 
> confusion for beginners" argument.  The confusion arises only
> when a
> single line comment is used to uncomment a set of characters
> that start
> with a special symbol.  That's a situation that doesn't arise
> that 
> often.  (I'd actually be very happy if the main sources of
> confusion fpr
> beginners where of such simple syntactic nature.)
> 
> Oh yes, it does happen that a single line comment begins with a
> special symbol. It has happened to me on several occations when using
> haddock annotation to my source code. It is all to easy to forget that
> extra space. With incomprehensible error messages as a result. 

I didn't say it doesn't happen.  I said, it doesn't happen that often.
Haddock increases the likelihood of it happening, but as Henrik wrote,
well just improve the errors messages a bit.  Errors involving operators
starting with -- could specifically suggest that the user might have
wanted a comment, but wrote an operator.

> As for consistency, well if you absolutely want to make it
> consistent,
> impose the same rule on {- as on --.
> 
> I still think there is an inconsistency here. And it has to do with
> maximal munch lexing. Maximal munch is what we normally expect from a
> lexer for a programming language. But the way comments work at the
> moment breaks maximal munch. The longest possible read is to read the
> whole line as a comment and not interpret for instance --^ as an
> operator. It breaks any programmers' intuition not only beginners'. I
> still get it wrong from time to time. 

That doesn't convince me either.  Comment syntax breaks standard lexical
analysis for nested comments anyway (as they are not regular).

And as I wrote before, if we were to design a language from scratch, I
might be persuaded to change my opinion, but if we change the rule for
Haskell now, we break good code.  I believe, we should not break good
code without a really good reason.  I haven't seen a really good reason
to change the status quo.

Manuel


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


Re: Comment Syntax

2006-02-02 Thread Arjan van IJzendoorn

If this really is a big problem for beginners, it would not seem
totally infeasible to add some special code that helpfully suggests
that a space perhaps ought to be inserted?


Here is what Helium says:

Warning: Syntax colouring usually can not handle names containing --
  Hint: If you wanted to start a comment, write spaces around --

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


Re: Comment Syntax

2006-02-02 Thread Josef Svenningsson
On 2/2/06, Henrik Nilsson <[EMAIL PROTECTED]> wrote:
Hi all,To corroborate Wadler's law further.:-) Josef wrote:
 > Oh yes, it does happen that a single line comment begins with a > special symbol. It has happened to me on several occations when using > haddock annotation to my source code. It is all to easy to forget that
 > extra space. With incomprehensible error messages as a result.But might that not just mean that the error messages ought to beimproved?I don't know how hard that would be, but after having played around
a bit with GHC, the messages I get are either of the type"parse error on input '--|'" or of the type "Not in scope: `-->'"(followed by lots of other stuff not being in scope etc).
If this really is a big problem for beginners, it would not seemtotally infeasible to add some special code that helpfully suggeststhat a space perhaps ought to be inserted?Or have you seen significantly worse error messages?
My point here was not that the error messages was that terrible.  I just wanted to point out to Manuel that it does happen that single line comments start with a symbol. Which makes the current comment syntax somewhat awkward.
Cheers,/Josef
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-01 Thread Creighton Hogg
On Thu, 2 Feb 2006, Henrik Nilsson wrote:

> Hi all,
> 
> To corroborate Wadler's law further.
> 
> Josef wrote:
> 
>  > Oh yes, it does happen that a single line comment begins with a
>  > special symbol. It has happened to me on several occations when using
>  > haddock annotation to my source code. It is all to easy to forget that
>  > extra space. With incomprehensible error messages as a result.
> 
> But might that not just mean that the error messages ought to be
> improved?
> 
> I don't know how hard that would be, but after having played around
> a bit with GHC, the messages I get are either of the type
> "parse error on input '--|'" or of the type "Not in scope: `-->'"
> (followed by lots of other stuff not being in scope etc).
> 
> If this really is a big problem for beginners, it would not seem
> totally infeasible to add some special code that helpfully suggests
> that a space perhaps ought to be inserted?
> 
> Or have you seen significantly worse error messages?

Well, if anecdotal evidence from a real live beginner would 
help, I've never had problems with the comments.
I think I made that mistake once, looked at the line it 
failed on, and added the space.


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


Re: Comment Syntax

2006-02-01 Thread Henrik Nilsson

Hi all,

To corroborate Wadler's law further.

Josef wrote:

> Oh yes, it does happen that a single line comment begins with a
> special symbol. It has happened to me on several occations when using
> haddock annotation to my source code. It is all to easy to forget that
> extra space. With incomprehensible error messages as a result.

But might that not just mean that the error messages ought to be
improved?

I don't know how hard that would be, but after having played around
a bit with GHC, the messages I get are either of the type
"parse error on input '--|'" or of the type "Not in scope: `-->'"
(followed by lots of other stuff not being in scope etc).

If this really is a big problem for beginners, it would not seem
totally infeasible to add some special code that helpfully suggests
that a space perhaps ought to be inserted?

Or have you seen significantly worse error messages?

Best,

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]

This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: Comment Syntax

2006-02-01 Thread John Meacham
On Thu, Feb 02, 2006 at 03:04:14AM +0100, Josef Svenningsson wrote:
> I new this response were coming It basically comes down to how one
> interprets the maximal munch. I know there are plenty of people who agree
> with you. But there are those that agree with my standpoint as well. I'm not
> going to propose that we start arguing about this. I suppose we'll have to
> use other arguments to persuade each other about the comment syntax.

isn't a conference coming up? I propose a round-robbin single
elimination arm wrestling match. I mean, it really is the only
definitive way to solve issues like comment syntax.

There will also be a karaoke competition to determine the fate of the
monomorphism restriction.

:)

John


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


Re: Comment Syntax

2006-02-01 Thread Josef Svenningsson
On 2/2/06, John Meacham <[EMAIL PROTECTED]> wrote:
On Thu, Feb 02, 2006 at 02:31:32AM +0100, Josef Svenningsson wrote:> I still think there is an inconsistency here. And it has to do with maximal> munch lexing. Maximal munch is what we normally expect from a lexer for a
> programming language. But the way comments work at the moment breaks maximal> munch. The longest possible read is to read the whole line as a comment and> not interpret for instance --^ as an operator. It breaks any programmers'
> intuition not only beginners'. I still get it wrong from time to time.huh? this is exactly the opposite. maximal munch means that it wouldconsume everything and then interpret it as an operator. having it the
other way would be a special case because you would have to stopconsuming input after the first --.I new this response were coming It basically comes down to how one interprets the maximal munch. I know there are plenty of people who agree with you. But there are those that agree with my standpoint as well. I'm not going to propose that we start arguing about this. I suppose we'll have to use other arguments to persuade each other about the comment syntax.
/Josef
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-01 Thread John Meacham
On Thu, Feb 02, 2006 at 02:31:32AM +0100, Josef Svenningsson wrote:
> I still think there is an inconsistency here. And it has to do with maximal
> munch lexing. Maximal munch is what we normally expect from a lexer for a
> programming language. But the way comments work at the moment breaks maximal
> munch. The longest possible read is to read the whole line as a comment and
> not interpret for instance --^ as an operator. It breaks any programmers'
> intuition not only beginners'. I still get it wrong from time to time.

huh? this is exactly the opposite. maximal munch means that it would
consume everything and then interpret it as an operator. having it the
other way would be a special case because you would have to stop
consuming input after the first --.

Though, I certainly think compilers could produce better error messages
when they see a line that begins with whitespace and then has an
operator starting with -- that leads to a type error. but that is not
really a language issue.

John


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


Re: Comment Syntax

2006-02-01 Thread Josef Svenningsson
I'm in favour of changing the comment syntax.On 2/2/06, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
I am against such a change.  The change would break existing software(eg, Yampa) and secondly I don't buy the "main sources of
confusion for beginners" argument.  The confusion arises only when asingle line comment is used to uncomment a set of characters that startwith a special symbol.  That's a situation that doesn't arise that
often.  (I'd actually be very happy if the main sources of confusion fprbeginners where of such simple syntactic nature.)Oh yes, it does happen that a single line comment begins with a special symbol. It has happened to me on several occations when using haddock annotation to my source code. It is all to easy to forget that extra space. With incomprehensible error messages as a result.
As for consistency, well if you absolutely want to make it consistent,impose the same rule on {- as on --.
I still think there is an inconsistency here. And it has to do with maximal munch lexing. Maximal munch is what we normally expect from a lexer for a programming language. But the way comments work at the moment breaks maximal munch. The longest possible read is to read the whole line as a comment and not interpret for instance --^ as an operator. It breaks any programmers' intuition not only beginners'. I still get it wrong from time to time.
Cheers,/JosefPS. This discussion is great as a data point for Wadler's Law.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-01 Thread John Meacham
On Wed, Feb 01, 2006 at 07:40:26PM -0500, Manuel M T Chakravarty wrote:
> As for consistency, well if you absolutely want to make it consistent,
> impose the same rule on {- as on --.

I think it is already consistant. '--' is a valid operator while '{-'
has no valid meaning outside of a comment initializer so it makes sense
that '--' would be a reserved operator while '{-' would be a syntatic
element.

John

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


Re: Comment Syntax

2006-02-01 Thread Manuel M T Chakravarty
I am against such a change.  The change would break existing software
(eg, Yampa) and secondly I don't buy the "main sources of  
confusion for beginners" argument.  The confusion arises only when a
single line comment is used to uncomment a set of characters that start
with a special symbol.  That's a situation that doesn't arise that
often.  (I'd actually be very happy if the main sources of confusion fpr
beginners where of such simple syntactic nature.)

As for consistency, well if you absolutely want to make it consistent,
impose the same rule on {- as on --.

Manuel

> My proposal is to make any text beginning '--' a comment (rather than  
> requiring a space after the two dashes.  I appreciate that the  
> argument against this is that various operators that look like this  
> are useful (e.g. -->).  However I think that any benefit gained by  
> operators like this is lost in confusion.
> 
> In order to back up my suggestion, I'd like to point out, that this  
> is indeed already how it is done for block comments.  i.e. we do not  
> expect {-> to be an operator, we expect it to be the beginning of a  
> comment.
> 
> Secondly, from my limited experience helping to teach Haskell, the  
> comment syntax is a primary source of confusion for beginners.   
> Beginners inevitably forget (or don't know) to add the space, and  
> will receive confusing errors about undefined symbols, or type  
> mismatches.  This is made yet more confusing by the fact that the  
> compiler appears to be pointing at an error in a comment.
> 
> Thanks
> 
> Tom Davie
> ___
> 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: 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: 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-30 Thread Antti-Juhani Kaijanaho
Thomas Davie wrote:
[they = novices]
> True but they're bound to get it wrong at least once (I know I did,  and
> damn were the errors confusing).

Of course they will. They will get a lot of other things wrong at least
once, too.

Syntax is syntax. So long as it's not preposterously complex, it's not
nearly the hardest part of the language to learn. And the current system
is, even if you disagree, consistent.

> Also, how do you propose that  --  is
> put on a slide and differentiated from --?

"Make sure you add a space after the two dashes."

> 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.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-01-30 Thread John Meacham
On Mon, Jan 30, 2006 at 06:42:44PM +, Thomas Davie wrote:
> I agree, this is not a great argument, but the fact that the language  
> is inconsistent, and that it confuses people easily, and can't come  
> up with great error messages when it does go wrong, (my original  
> arguments) really are good arguments for fixing this.

I don't see how it is inconsistant at all.

-- makes sense as a reserved operator because if it wern't a comment
then '--' would be a valid operator. however {- would not be a valid
operator if it were not a comment starter so it makes sense that it
would act differently. the current system seems quite consistant and
reasonable to me.

John

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


Re: Comment Syntax

2006-01-30 Thread Thomas Davie


On Jan 30, 2006, at 7:53 PM, Henrik Nilsson wrote:


Hi all,

Neil Mitchell wrote:

> Really? Using hoogle I can't find any operators that have -- as a
> substring.

For what's it worth, Yampa uses --> (along with >--).


Similarly fwiw, Simon said something along the lines of Haskell98 ->  
Haskell' being an interesting refactoring for HaRe in the last  
meeting... But don't quote me on that, it was probably just a random  
musing.


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


Re: Comment Syntax

2006-01-30 Thread Henrik Nilsson

Hi all,

Neil Mitchell wrote:

> Really? Using hoogle I can't find any operators that have -- as a
> substring.

For what's it worth, Yampa uses --> (along with >--).

Best,

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: Comment Syntax

2006-01-30 Thread Sebastian Sylvan
On 1/30/06, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> > Yes, I buy those arguments.  But it's also rather convenient to be
> > able to use -- in operators.
>
> Really? Using hoogle I can't find any operators that have -- as a substring.

The operator "-->" certainly is a very good symbol for many things. I
think the reason it isn't used more has less to do with weather "--"
is useful in symbols, and more to do with the fact that "-- " is
de-facto used as the line-comment and people try to avoid naming their
operators in ways which may confuse people (and syntax highlighing in
some editors :-))

/S

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


Re: Comment Syntax

2006-01-30 Thread Neil Mitchell
> Yes, I buy those arguments.  But it's also rather convenient to be
> able to use -- in operators.

Really? Using hoogle I can't find any operators that have -- as a substring.

And some text editors can't handle regular expressions for syntax
definitions, in the same way that some editors don't provide a
psychiatrist, mail reader and game of tetris :)

Thanks

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


Re: Comment Syntax

2006-01-30 Thread lennart

Quoting Thomas Davie <[EMAIL PROTECTED]>:

I agree, this is not a great argument, but the fact that the language 
 is inconsistent, and that it confuses people easily, and can't come  
up with great error messages when it does go wrong, (my original  
arguments) really are good arguments for fixing this.


Yes, I buy those arguments.  But it's also rather convenient to be
able to use -- in operators.

   -- Lennart

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


Re: Comment Syntax

2006-01-30 Thread Thomas Davie


It gives you regexp and nothing more - this makes it a pain in  
the  arse to input every possible character that is/isn't allowed.


Bob



Oh, come on.  It's a one time pain.  How hard can it be?


I agree, this is not a great argument, but the fact that the language  
is inconsistent, and that it confuses people easily, and can't come  
up with great error messages when it does go wrong, (my original  
arguments) really are good arguments for fixing this.


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


Re: Comment Syntax

2006-01-30 Thread lennart

Quoting Thomas Davie <[EMAIL PROTECTED]>:



On 30 Jan 2006, at 14:49, [EMAIL PROTECTED] wrote:


Quoting Thomas Davie <[EMAIL PROTECTED]>:



On 30 Jan 2006, at 14:28, Neil Mitchell wrote:


Another argument in favour of this is that most editors with  syntax
hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax
highlighting, this isn't a big problem. The editor will tell you  (if
the highlighting is implemented correctly) that --> does not  start a
comment. Rather than changing the language we should fix the
highlighting modes for the editors in question.


This is rather hard, unless your editor is actually a thinly  disguised
programming language. Certainly for my editor of choice (TextPad)  this
cannot be done easily - and isn't needed for most other languages.


Ditto the SubEthaEdit syntax highlighting mode - I guess most  
people  have got used to editors being thinly disguised operating  
systems  these days (not looking at emacs or vim here).




Are you telling me that your text editor doesn't even give you a  regexp
for defining comments?  If it doesn't, I'd say your editor needs to  upgrade
to some good 1960s text editor technology.


It gives you regexp and nothing more - this makes it a pain in the  
arse to input every possible character that is/isn't allowed.


Bob



Oh, come on.  It's a one time pain.  How hard can it be?

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


Re: Comment Syntax

2006-01-30 Thread Taral
On 1/30/06, Thomas Davie <[EMAIL PROTECTED]> wrote:

> It gives you regexp and nothing more - this makes it a pain in the
> arse to input every possible character that is/isn't allowed.

Steal it from places (vim):

syn match   hsLineComment  "---*\([^-!#$%&\*\+./<=>[EMAIL 
PROTECTED]|~].*\)\?$"

--
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: Comment Syntax

2006-01-30 Thread Thomas Davie


On 30 Jan 2006, at 14:49, [EMAIL PROTECTED] wrote:


Quoting Thomas Davie <[EMAIL PROTECTED]>:



On 30 Jan 2006, at 14:28, Neil Mitchell wrote:

Another argument in favour of this is that most editors with  
syntax

hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax
highlighting, this isn't a big problem. The editor will tell you  
(if
the highlighting is implemented correctly) that --> does not  
start a

comment. Rather than changing the language we should fix the
highlighting modes for the editors in question.


This is rather hard, unless your editor is actually a thinly  
disguised
programming language. Certainly for my editor of choice (TextPad)  
this

cannot be done easily - and isn't needed for most other languages.


Ditto the SubEthaEdit syntax highlighting mode - I guess most  
people  have got used to editors being thinly disguised operating  
systems  these days (not looking at emacs or vim here).




Are you telling me that your text editor doesn't even give you a  
regexp
for defining comments?  If it doesn't, I'd say your editor needs to  
upgrade

to some good 1960s text editor technology.


It gives you regexp and nothing more - this makes it a pain in the  
arse to input every possible character that is/isn't allowed.


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


Re: Comment Syntax

2006-01-30 Thread lennart

Quoting Thomas Davie <[EMAIL PROTECTED]>:



On 30 Jan 2006, at 14:28, Neil Mitchell wrote:


Another argument in favour of this is that most editors with syntax
hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax
highlighting, this isn't a big problem. The editor will tell you (if
the highlighting is implemented correctly) that --> does not start a
comment. Rather than changing the language we should fix the
highlighting modes for the editors in question.


This is rather hard, unless your editor is actually a thinly disguised
programming language. Certainly for my editor of choice (TextPad) this
cannot be done easily - and isn't needed for most other languages.


Ditto the SubEthaEdit syntax highlighting mode - I guess most people  
have got used to editors being thinly disguised operating systems  
these days (not looking at emacs or vim here).




Are you telling me that your text editor doesn't even give you a regexp
for defining comments?  If it doesn't, I'd say your editor needs to upgrade
to some good 1960s text editor technology.

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


Re: Comment Syntax

2006-01-30 Thread Thomas Davie


On 30 Jan 2006, at 14:28, Neil Mitchell wrote:


Another argument in favour of this is that most editors with syntax
hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax
highlighting, this isn't a big problem. The editor will tell you (if
the highlighting is implemented correctly) that --> does not start a
comment. Rather than changing the language we should fix the
highlighting modes for the editors in question.


This is rather hard, unless your editor is actually a thinly disguised
programming language. Certainly for my editor of choice (TextPad) this
cannot be done easily - and isn't needed for most other languages.


Ditto the SubEthaEdit syntax highlighting mode - I guess most people  
have got used to editors being thinly disguised operating systems  
these days (not looking at emacs or vim here).


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


Re: Comment Syntax

2006-01-30 Thread Neil Mitchell
> > Another argument in favour of this is that most editors with syntax
> > hilighting will show --> as a comment, which again increases the
> > confusion factor.
>
> I would rather argue that since we have editors with syntax
> highlighting, this isn't a big problem. The editor will tell you (if
> the highlighting is implemented correctly) that --> does not start a
> comment. Rather than changing the language we should fix the
> highlighting modes for the editors in question.

This is rather hard, unless your editor is actually a thinly disguised
programming language. Certainly for my editor of choice (TextPad) this
cannot be done easily - and isn't needed for most other languages.

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


Re: Comment Syntax

2006-01-30 Thread Thomas Davie


On 30 Jan 2006, at 14:01, Antti-Juhani Kaijanaho wrote:


Thomas Davie wrote:
Except that there is a good reason (pos two) why the language is   
wrong
- it's inconsistant with the other comment syntax, and it's   
confusing

to newbies.


I tend to think of "--" as a reserved word in the same sense as "case"
is a reserved word. Hence, -- starts a comment, --> doesn't. The  
opening

brace ({) is not a symbol character, so {- is in the same category as
the semicolon, special symbol, not a reserved word.

I was actually delighted to learn that it works like this.

For newbies, just tell them that "-- " is the comment starter. It  
works
well enough, and newbies get a lot of other half-truths, so it's  
nothing

earth-shattering :)


True but they're bound to get it wrong at least once (I know I did,  
and damn were the errors confusing).  Also, how do you propose that  
--  is put on a slide and differentiated from --?


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


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


Re: Comment Syntax

2006-01-30 Thread Antti-Juhani Kaijanaho
Thomas Davie wrote:
> Except that there is a good reason (pos two) why the language is  wrong
> - it's inconsistant with the other comment syntax, and it's  confusing
> to newbies.

I tend to think of "--" as a reserved word in the same sense as "case"
is a reserved word. Hence, -- starts a comment, --> doesn't. The opening
brace ({) is not a symbol character, so {- is in the same category as
the semicolon, special symbol, not a reserved word.

I was actually delighted to learn that it works like this.

For newbies, just tell them that "-- " is the comment starter. It works
well enough, and newbies get a lot of other half-truths, so it's nothing
earth-shattering :)

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


Re: Comment Syntax

2006-01-30 Thread Thomas Davie


On 30 Jan 2006, at 13:51, Ulf Norell wrote:



On Jan 30, 2006, at 1:30 PM, Neil Mitchell wrote:


Another argument in favour of this is that most editors with syntax
hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax  
highlighting, this isn't a big problem. The editor will tell you  
(if the highlighting is implemented correctly) that --> does not  
start a comment. Rather than changing the language we should fix  
the highlighting modes for the editors in question.


Except that there is a good reason (pos two) why the language is  
wrong - it's inconsistant with the other comment syntax, and it's  
confusing to newbies.


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


Re: Comment Syntax

2006-01-30 Thread Ulf Norell


On Jan 30, 2006, at 1:30 PM, Neil Mitchell wrote:


Another argument in favour of this is that most editors with syntax
hilighting will show --> as a comment, which again increases the
confusion factor.


I would rather argue that since we have editors with syntax  
highlighting, this isn't a big problem. The editor will tell you (if  
the highlighting is implemented correctly) that --> does not start a  
comment. Rather than changing the language we should fix the  
highlighting modes for the editors in question.


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


Re: Comment Syntax

2006-01-30 Thread Neil Mitchell
Another argument in favour of this is that most editors with syntax
hilighting will show --> as a comment, which again increases the
confusion factor.

Thanks

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


Re: Comment Syntax

2006-01-30 Thread Lennart Augustsson

That's the way it used to be, and I agree it's more consistent.

Thomas Davie wrote:
I would like to suggest a different change to single line comment  
syntax to do two things.  First, address an inconsistency with multi  
line comments, and secondly remove one of the main sources of  confusion 
for beginners.


My proposal is to make any text beginning '--' a comment (rather than  
requiring a space after the two dashes.  I appreciate that the  argument 
against this is that various operators that look like this  are useful 
(e.g. -->).  However I think that any benefit gained by  operators like 
this is lost in confusion.


In order to back up my suggestion, I'd like to point out, that this  is 
indeed already how it is done for block comments.  i.e. we do not  
expect {-> to be an operator, we expect it to be the beginning of a  
comment.


Secondly, from my limited experience helping to teach Haskell, the  
comment syntax is a primary source of confusion for beginners.   
Beginners inevitably forget (or don't know) to add the space, and  will 
receive confusing errors about undefined symbols, or type  mismatches.  
This is made yet more confusing by the fact that the  compiler appears 
to be pointing at an error in a comment.


Thanks

Tom Davie
___
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