Re: [Haskell-cafe] Re: [Haskell] MR details (was: Implicit type of numeric constants)

2006-09-25 Thread Christian Sievers
Bernie Pope answered:

  1. Why do the rules of the monomorphism restriction explicitly mention
 *simple* pattern bindings?
 Where is the difference, especially as there is a translation to
 simple pattern bindings?
 Why should
 
 p | a==b  = 2
   | otherwise = 3
 
 be treated different than
 
 p = if a==b then 2 else 3
 
 
 They are the same (both are simple pattern bindings). The report says  
 in section 4.4.3.2 that the first can be translated into the second.

Indeed, I meant to allude to this translation.

 A simple pattern binding is one where the lhs is a variable only.

That's consistent with the second reason for rule one of the MR.

However, the mentioned section 4.4.3.2 defines it differently:

   A simple pattern binding has form p = e.

And if there is any doubt about what p stands for, it goes on:

   The pattern p ...

Contrasting to that:

   The general form of a pattern binding is p match, where a match is the same
   structure as for function bindings above; in other words, a pattern binding
   is: 
 
   p| g1= e1
| g2= e2
...
| gm= em
where { decls }


So according to this definition, a pattern binding is simple iff
there are no guards (unless they are in the expression).
Also the translation to a simple pattern binding only gets rid of guards.

So there seems to be an error in the report, which can be fixed by either
redefining simple pattern binding, or using a differnet description in the
MR.


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


[Haskell] MR details (was: Implicit type of numeric constants)

2006-09-23 Thread Christian Sievers
Hello,

I don't take my advice to go to haskell-cafe  :-)

The discussion continued outside the mailing list, and now I have
two questions myself:

1. Why do the rules of the monomorphism restriction explicitly mention
   *simple* pattern bindings?
   Where is the difference, especially as there is a translation to
   simple pattern bindings?
   Why should

   p | a==b  = 2
 | otherwise = 3

   be treated different than

   p = if a==b then 2 else 3

2. The gentle introduction says in section 12.3:
   An identifier is monomorphic if is either not overloaded, or is overloaded
   but is used in at most one specific overloading and is not exported.

   How does that relate to the report?

Maybe I have to withdraw what I said about haskell being well defined.


All the best
Christian Sievers
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Trying to write a TCP proxy

2006-09-23 Thread Christian Sievers
John Ky wrote:

 I finally realised that hGetLine strips out the \n newline character
 so when I forward the line to the server, I need to append it again.

Or use hPutStrLn instead of hPutStr ?
(I may be missing something...)


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


Re: [Haskell-cafe] Polymorphism/monomorphism (and the restriction)

2006-09-23 Thread Christian Sievers
Aaron McDaid wrote:

 This code experiments with Int, Float and (Num a) = a, and I 
 tried to print x*2 and x/2 for each. (4::Int)/2 isn't allowed because / 
 isn't defined for Ints.

More exactly: (/) is a member function of the Fractional class, and Int is not
an instance of this class.

 You can see that
  kN :: (Num a) = a
 took two different types depending on what method ( / or * ) was applied 
 to it.
  kN / 2 = 2.0
  kN * 2 = 8
 kN/2 is a Float (it can't use Int as / isn't defined for Int, so it uses 
 Float, for which / is defined).

kN/2 has type  Fractional a = a  (try :t kN/2 in ghci)
and when you apply it to show, a specific type will be chosen
by defaulting (Haskell report section 4.3.4).
Without an explicit default declaration, Haskell will try first Integer, then
Double.  Integer is not an instance of Fractional, so Double will be used.

You will get the types you claim to get when you add the line
default (Int,Float) at the top of your file.

 kN*2 is an Int.

By itself, it's  Num a = a,  then it will default to Integer.

 The above outputs demonstrates polymorphism, doesn't it? i.e. Not only 

Polymorphism (or rather: overloading) and defaulting.

 has the compiler got a variety of types to choose from, but a variety of 
 types can be used at runtime?

It only chooses (i.e. tries in order) the types given in the (posibly implicit)
default declaration.  At runtime it doesn't care about types, but of course
the same polymorphic or overloaded function can be used with different types.

 The interesting thing is that k behaves as a Float in both cases. This 
 is monomorphism isn't it? i.e. the compiler may have a variety of types 
 to choose from, but it picks one and sticks to it for every usage. In 
 summary, k didn't give the same outputs as kN.

Since (/) is used with k, it must be Fractional, so as in kN/2,
defaulting makes it Double.

 I'm fairly new to these lists, so apologies if I'm covering old ground 
 again. My first aim is to understand exactly what polymorphism and 
 monomorphism is and demonstrate corresponding results, before thinking 
 about the restriction.

The type of   map :: (a - b) - [a] - [b]
is polymorphic.
Here we are talking about overloading, also known as
ad-hoc polymorphism.  In Haskell overloaded functions
are recognizable by the context in their type, e.g.:
   abs :: Num a = a - a

I think I also mixed this up in one of my earlier mails.
Seems we need a glossary.


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


Re: [Haskell] Re: Implicit type of numeric constants

2006-09-21 Thread Christian Sievers
Robert Stroud wrote:

 Thanks - that's a helpful example. But why is the following not  
 equivalent to the untyped k = 2 case:
 
 let f :: Int - Int - Int ; f x y = x * y in (f 2 2, 1/2)
 
 Does the type of 2 effectively get decided twice, once as an Int, and  
 once as a Fractional, and is this the repeated computation that the  
 monomorphism restriction is intended to prevent?

2 has the fixed polymorphic type  Num a = a, which gets resolved
at each occurance.  This resolving happens at compile time, so there
is no repeated computation at run time involved.  However, you need
to somehow get both a 2::Int and a 2::Double which may be seen as a
trivial case of this repeated computation.

 Otherwise, I would have expected that it wouldn't make any difference  
 whether I used a named 2 or an anonymous 2, but imposing the  
 monomorphism restriction on the named 2 seems to break referential  
 transparency.

Only if you expect referential transparency for implicitly typed values.
All you have to do is say

  k :: Num a = a
  k = 2

and everything is fine.


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


Re: [Haskell] Re: Implicit type of numeric constants

2006-09-20 Thread Christian Sievers
Arie Peterson wrote:

  However, if I type an apparently equivalent let expression into Hugs
  directly, then I get the value 4 as expected
 
  let k = 2 ; f :: Int - Int - Int ; f x y = x * y in f k k
 
  Why is there a difference in behaviour?
 
 Here, there is no defaulting, 'k' has the polymorphic type you expect, and
 the use of 'k' as an argument to the monomorphically typed 'f' chooses the
 right instance of 'Num'.

Well, there is no defaulting at the stage of type checking when k is given
type Num a = a, the monomorphism restriction applies and this type is not
generalised to forall a . (Num a) = a, then the use of k forces the type
variable a to be Int, and then there is no longer any need for defaulting.

So k gets a monotype which is determined by its usage, you cannot do e.g.

  let k = 2 ; f :: Int - Int - Int ; f x y = x * y in (f k k, 1/k)

whereas   let k :: Num a = a; k = 2; ...   is possible.


Defaulting in Haskell 98 happens so late that this file

  k = 2
  f :: Int - Int - Int
  f x y = x * y
  r = f k k

is okay.  Alas, Hugs does not comply in this respect, see
http://cvs.haskell.org/Hugs/pages/users_guide/haskell98.html
at the end of 5.1.3.


All the best,
Christian Sievers
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Implicit type of numeric constants

2006-09-20 Thread Christian Sievers
Robert Stroud wrote:

 However, I still think there's a bit of an inconsistency here. I  
 understand that if k had the type Num a = a, then the expression  
 show k would be ambiguous, but unless I write that expression,  
 there's no ambiguity...

Actually, you can give k that type, and thanks to defaulting you
can then still use  show k.

 So it seems to me that the type checker is being a bit too eager to  
 prevent something that hasn't happened yet.

Here it is the monomorphism restriction (Haskell report section 4.5.5)
that enforces defaulting.

 In contrast, in the case where I write let k = 2 ..., the type  
 checker seems happy to resolve the polymorphic type within the  
 context of the let expression, and does what I expect.

I hope my last mail explained this: defaulting for monomorphic types
happens quite late.

 So is the problem that the context is effectively unbounded when I  
 load the definition from a file, and hence the type checker has to be  
 very conservative about preventing the ambiguity?

A file is (essentially) a module.  This defaulting happens
when type inference for an entire module is complete
(rule 2 of the above mentioned section), because we don't
want types to depend on arbitrary other modules - think of
seperate compilation.

 I'm afraid I'm also still not clear about why 2 doesn't default to  
 2::Integer in the same way that k defaults to k::Integer,

It does, that's why   show 2   works.


Hope that helps
Christian Sievers
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-05 Thread Christian Sievers
Dominic Steinitz asked:

 Is asTypeOf really Haskell 98?

Yes, it is in the Prelude.
And there is no special magic, it is Haskell-98-implementable, see
http://haskell.org/onlinereport/standard-prelude.html#$vasTypeOf


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


Re: In search of: [a-b] - a - [b]

2003-06-20 Thread Christian Sievers
Derek Elkins wrote:

   flist :: [a-b] - a - [b]
   flist fs a = map (flip ($) a) fs
 or much nicer (IMO) 
   flist fs a = map ($ a) fs 

This is a case where I'd prefer a list comprehension:

flist fs a = [ f a | f - fs ]

(and this could be a monad comprehension, if Haskell still had them...)

 the generalized solution being simply,
 f mf x = do
 f - mf
 return (f x)

Or just replace map by fmap in your flist from above.


All the best
Christian Sievers
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: avoiding cost of (++)

2003-01-17 Thread Christian Sievers
Hal Daume III asked:

  mapWithout :: ([a] - b) - [a] - [b]
  mapWithout f = mapWith' []
  where mapWith' pre [] = []
mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
 
 Unfortunately, this is very slow, due to the overhead of (++).
 
 Any way I could speed this up would be great.  Note that order doesn't
 matter to 'f', but I do need that the order in which the elements of the
 list are processed be the same as in map.

If f is associative, i.e.  f (l1++l2) == f [f l1, f l2]
(this forces a=b), you can do

mapWithout :: ([a] - a) - [a] - [a]
mapWithout f l = let n  = f [] -- neutral element
 b x y = f [x,y]   -- binary version
 sl = scanl b n l
 sr = scanr b n l
 in zipWith b sl (tail sr)

You'll probably rather use
mapWithout' (a-a-a) - a - [a] - [a]
mapWithout'  bin_op   neutral  l = ...

If f is not defined for empty lists, you can combine (with a bit more work)
the results of scanl1 and scanr1.


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



Re: precedence bug with derived instances

2002-10-31 Thread Christian Sievers
Dean Herington wrote:

  Why is that expression not type-correct?
 
 [Answering my own question...]
 
 Duh.  Because the type doesn't partake of Eq.

Right.  Of course, it's a different kind of error than for example
 [Orange] == Orange ---  where no Eq Color instance decl would help,
and I wonder if there is a special name for it.


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



Re: Question about use of | in a class declaration

2002-08-21 Thread Christian Sievers

Simon Guest asked:

 Please could someone explain the meaning of | in this class declaration (from 
Andrew's example):
 
   class (Ord k) = Map m k v | m - k v where
 lookupM :: m - k - Maybe v
 
 I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
Haskell 98 report.  Any references?

It might not have become clear from the previous answers:
this construction is not Haskell 98, but an extension.
That's why it's not in the report.

BTW: Already multi parameter type classes 
(such as  class (Ord k) = Map m k v where ...)
^ ^ ^ only one type variable allowed here
aren't Haskell 98.


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



Re: defining (- Bool) as a set

2002-04-23 Thread Christian Sievers

Hal Daume III wrote:

 I'd like to be able to define something like

   single x = \y - if x == y then True else False

Just a note on style: it always hurts me to see something like

  if term then True else False

-- this is just the same as 'term'.

So you could say

  single x = \y - x==y

which is in turn just the same as

  single x = (x==)

which is, amazingly, nothing more than

  single = (==)

-- one can debatte whether this is still better style than the first variant,
but it's surely interesting to realize.


All the best,
Christian Sievers
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell 98 Report: October release

2001-10-04 Thread Christian Sievers

Simon Peyton-Jones wrote:

 Feedback please...

One typo:

In the change for
   Page 93, Appendix A, Standard Prelude
the comment should not talk about a fixtity declaration.
^


Bye
Christian Sievers

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



Re: FW: Haskell 98 report problem re lexical structure.

2001-07-25 Thread Christian Sievers

Simon Peyton-Jones proposed:

 1.  I will use lexeme consistently to mean what the lexeme
 production means.
That's good.

 2.  The place that lexeme is currently used inconsistently is in 2.3
 (Comments)  Here I propose to replace paras 2 and 3 thus:
  
 An ordinary comment begins with a sequence of two or more consecutive
 dashes (e.g. --) and extends to the following newline. The sequence of
 dashes must not be the prefix of a legal lexeme. For example,

Any number of dashes is a prefix of a legal lexeme.
You want to talk about what follows, but this formulation is about
what might follow. (Or at least, that's how I understand it.)
How about something like:
The sequence of dashes must not be followed by another symbol,
for example -- or --| do not begin a comment, they are just ordinary
lexemes.

 5.  [Re Christian S's proposal, which I sent earlier, remove opencom
 from lexeme]

That is consisted with the other change you suggested in 2., and
indeed a nicer way to be so.


The second sentence in 5.5.1 reads
Since qualifier names are part of the lexical syntax, no spaces are
allowed between the qualifier and the name.

I think this should be
Since qualified names...
  ^
and could as well be
Since qualified names are lexemes, no spaces are allowed...


All the best
Christian Sievers

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



Re: lexical description problem in language report?

2001-07-24 Thread Christian Sievers

Thomas Hallgren wrote:

   program -  {lexeme | whitespace }
   lexeme  -  varid | conid | varsym | consym | literal | special | 
 reservedop | reservedid
 
 There is no reference to qualified names here. I thought the purpose of 
 these productions were to say that a Haskell program is correct on the 
 lexical level iff there is a derivation of it in the lexical grammar, 
 starting from the nonterminal program. Since qualified names are not 
 part of this grammar, they are not part of the lexical syntax, which 
 contradicts the text in section 5.5.1.
 
 So, I repeat my improvment suggestions: include qvarid, qconid, etc, in 
 the production for lexeme. Move the explanation of the lexical 
 properties of qualified names from section 5.5.1 to section 2.4.

You could still parse a qualified name as three lexemes.
Of course you don't want this, as this would allow white space
between them.
For the same reason, you want backquoted functions and constructors
to be only one lexeme. In order to achieve this, just use qop instead
of qvarsym and qconsym. And we need opencom, as the report says {- is
a lexeme.

So I suggest:

  lexeme  - qvarid  | qconid  | qop
   | literal | special | reservedop | reservedid | opencom


It's all not new. See:
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01596.html
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01730.html


All the best
Christian Sievers

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



Re: Typo in haskell98-report/standard-prelude.html

2000-03-07 Thread Christian Sievers

Marcin 'Qrczak' Kowalczyk wrote:
 
 The name sum in the export list of PreludeList is spelled Sum
 (uppercase).

That's already mentioned on the Errata page at
http://research.microsoft.com/~simonpj/haskell/haskell98-bugs.html

It says:
Page 105, Appendix A.1, line 11. In the module header for PreludeList
replace "Sum" by "sum". 


Christian Sievers



Re: concurrency (was OO in Haskell)

1999-10-07 Thread Christian Sievers

Tim [EMAIL PROTECTED] wrote:

 For example, consider a program where one thread prints a value from an MVar,
 while another thread modifies it. The output of the program will vary from one
 run to another, even though its input (none) is unchanged.

This is not a result of using concurrency.
You see the same no input/different output behaviour in a program as
simple as this:

 import Random
 main = getStdRandom (randomR (False,True)) = print

(Or use the Time library.)

And nothing of this breakes referential transparency.
For example, 

 main = randomints = print
 randomints :: IO (Int,Int)
 randomints = do a - getStdRandom (randomR (1,100))
 b - getStdRandom (randomR (1,100))
 return (a,b)

has the same possible results as

 main = randomints = print
 randomints :: IO (Int,Int)
 randomints = let rnd = getStdRandom (randomR (1,100)) in
  do a - rnd; b - rnd  
 return (a,b)

Each time a program is run it is given a different world to start
with.
C is as referentially transparent as you are willing to agree that
each function has an implicit IO in its type, which won't gain you
anything. Even that is not really enough. "volatile" variables are
MVars, and what are non-volatile variables changed in signal
handlers? Uncaught type errors? Enough of that.

All the best,
Christian Sievers






Re: Haskell Wish list: library documentation

1999-09-09 Thread Christian Sievers

Two poeple suggested to use Strings in the example for unzip,
(and they even suggested the same strings!)

  unzip [("a", 1), ("b", 2), ("c", 3)] = (["a", "b", "c"], [1, 2, 3])

This is better, but now beginners might get the impression that "c"
is the way to name a Char, so I suggest to change this to

   unzip [("", 1), ("a", 2), ("aa", 3)] = (["", "a", "aa"], [1, 2, 3])

which even is no longer!


All the best,
Christian Sievers





Re: Monads in plain english (Was: Re: Licenses and Libraries)

1999-09-01 Thread Christian Sievers

  Indeed.  But if you get this far, understanding (=) quite trivial
  (assuming you don't have problems with higher-order functions).
 Yes, it would be quite trivial.  But why bother?  You only need (=)
 if you want to declare your own instance of Monad, which probably doesn't
 need to be in an introductory course.

I think I would feel quite unsatisfied if I didn't know that 'do' is
not some strange feature which seems to be unrelated to the rest, but
only some syntactic sugar for very normal higher order combinators.

And even if propably none ever needs it, I feel much happier to know
that 'zipWith (=)' is there and doesn't have to be written in
do-syntax. This is what reassures me that 'IO a' is an abstract, but
otherwise normal data type.

It may be useful, in the beginning of a course, to tell the students
how to do some simple IO using 'do' in a recipe like manner. (But if
they are using an interpreter and don't have to write a main function,
you can as well leave this out.) But in order to explain monads even
to someone who wouldn't define his own, I'd surely not conceal (=).


Alll the best,
Christian Sievers





Re: Units of measure

1999-08-26 Thread Christian Sievers

Anatoli Tubman wrote:

 I once wrote a C++ template library that did exactly that.  Arbitrary units,
 rational exponents -- you can have (m^(3/2)/kg^(5/16)) dimensioned value.
 All at compile time, without runtime checking whatsoever.

Is there any sense physically in rational exponents?
If not, we could use this extra information for less permissive type
checking, for example only allowing a square root from an argument
that has only even exponents.
(Cayenne doesn't happen to have c*n-patterns?)

Christian Sievers





Re: Units of measure

1999-08-26 Thread Christian Sievers

  (Cayenne doesn't happen to have c*n-patterns?)
[ ;-) forgotten.]
 `c*n' and `n+k' are equally abominable.  Cayenne has neither.

I thought they might be nice to express the type of sqrt.
When we have the type as

 Unit (mass::Int) (length::Int) (time::Int) = Double

it should be s.th. like  Unit (2*m) (2*l) (2*t) - Unit m l t.
Now I realized that the type does indeed nearly look like that, but
without using any doubtful pattern matching features:

  sqrt  ::  (m::Int)  |-  (l::Int)  |-  (t::Int)  |-
Unit (2*m) (2*l) (2*t)  -  Unit m l t

(Will hidden arguments work in this case?)

I really like Cayenne.


All the best,
Christian Sievers





Re: Haskell MIME types?

1999-08-25 Thread Christian Sievers

Alexander Jacobson wrote:

 Postscript interpreters also have the ability to execute rm *.
 The difference is that postscript interpreters have a command line option
 to turn off file system access capabilities.
 Is there a command line option in hugs to disallow import of System?

I don't think disallowing some imports is the way to go. For example,
you also have Directory.removeFile, but I'd rather not suggest to
disallow importing Directory. Instead, operations that an untrusted
code shouldn't execute could raise an exeption like isPermissionError
or isIllegalOperationError. In *nix-land, we might chose to just run
Hugs under its own UID, so it might even write its own files, and
delete them, but only them.

  On Tue, 24 Aug 1999, Fritz K Ruehr wrote:
  
   | I just convinced my local sysadmin to attach a new MIME type to
   | outgoing Haskell programs sent by our web server, namely
   | "application/x-haskell".

Maybe the Haskell-Version should also go into the MIME type name, as
in "application/x-haskell98".


All the best,
Christian Sievers





Re: The dreaded layout rule

1999-08-03 Thread Christian Sievers

I wrote:

 lexeme  - qvarid | qconid | qvarsym | qconsym
  | literal | special | reservedop | reservedid 
 
 Now we could replace qvarsym and qconsym by qop, and have both
 examples parse in the same way. However, unlike the other change in
 lexeme's definition, I don't suggest this, I only want to point out
 that there is a (formally) simple way out of the present somewhat
 inconsistent state.

I changed my mind about this issue, I do suggest to change it as
proposed, for if `elem` were three lexemes, any whitespace between
them would be allowed. This might even be considered a typo, as I
think no one intended to allow expressions like

 x ` {- look ma -} elem   -- comments inside!
   ` l 


All the best,
Christian Sievers





Re: Strange lexical syntax

1999-06-28 Thread Christian Sievers

Simon Marlow wrote:

 Quick quiz:  how many Haskell lexemes are represented by the following
 sequences of characters?
 
   1)  M.x
   2)  M.let
   3)M.as
   4)  M..
   5)  M...
   6)  M.!
 
 answers:
   
   1)  1.  This is a qualified identifier.

We all know what M.x means, but recently I wondered about how the
report makes this sure. I'm afraid it doesn't.

Of course, there is section "5.5.1 Qualified names" saying:

A qualified name is written as modid.name. Since qualifier names are
part of the lexical syntax, no spaces are allowed between the
qualifier and the name. Sample parses are shown below.

[I guess "qualifier names" should be "qualified names".]
 
But this seems to be an explanation, not an additional information.
The second sentence seems to say M.x is a lexeme, as they are the
fundamental items of lexical analysis.
(Section "2.2 Lexical Program Structure": At each point, the longest
 possible lexeme satisfying the lexeme production is read, using a
 context-independent deterministic lexical analysis ...)

And if it weren't a lexeme, we're really in trouble, because:
Any kind of whitespace is also a proper delimiter for lexemes.

Still it isn't. It surely is a qvarid, but lexeme is defined like
this: 

lexeme  - varid | conid | varsym | consym
 | literal | special | reservedop | reservedid 

A varid is unqualified, and it is also none of the others.

So maybe this should be:
lexeme  - qvarid | qconid | qvarsym | qconsym
 | literal | special | reservedop | reservedid 

And then I guess we should have   qtyc{on,ls} - qconid .

Am I terribly missing something?

   2)  3. 'let' is a keyword, which excludes this string
  from being a qualified identifier.

That's really ugly. I never thought about such things.
Good you finally uncovered it.

   3)  1. 'as' is a "specialid", not a "reservedid".
 
   4)  1. This is a qualified symbol.
 
   5)  2. '..' is a reserved operator, so a qualified symbol
  is out.  The sequence '...' is a valid operator and
  according to the maximal munch rule this must be
  the second lexeme.
 
   6)1. '!' is a "specialop", not a "reservedop".
 
 
 I especially like case 5 :-)

Yes, it's amazing! Why didn't you go on? M is a qualified symbol?

 This is pretty bogus.  I suggest as a fix for Haskell 2 that all of the
 above be treated as 1 lexeme, i.e. qualified identifiers/symbols.

But what would M.let mean? Module M can't define let, neither this way
  M.let = ...  -- qualiefied name not allowed
nor that:
  let = ...-- let is reserved 

However, 'let' does mean something in module M, so a strange option is
to let 'M.let' mean 'let'.

Should we just disallow it?


There is still another problem in the report.
Section "2.3 Comments" says:
A nested comment begins with the lexeme "{-" ...

There is no such lexeme.
We'd need  lexeme - ... | opencom


What does M.-- mean?


All the best,
Christian Sievers
-- 
Freeing Software is a good beginning. Now how about people?





Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Christian Sievers

 So, the name of a type is always at least a full word, as are the names of
 specific functions.  But type variables are almost always single
 characters, and distinct from the names of any type.  Conventionally, they
 are also usually "a", "b", and "c", although "m" is for monad.
 Conventionally also, generic function arguments are "f" and "g", the
 conventional predicate is "p". Generic arguments are "x" and "y" (or "xs"
 and "ys" if they are lists); arguments with specified types are usually
 the first letter of their type name (e.g., "c" for Char, "i" for an Int;
 "n" and "m" are indices)... that covers most of it, I think.

I've never thought about a difference between i (and j) on the one
hand and n and m on the other, besides I would use i, j more locally,
if there were such a difference. So I might use i-[1..n], but would
nearly never use  n-[1..i].
If I don't do pattern matching on a list, I sometimes use l.
Otherwise, I use (a:as) as well as (x:xs) for lists.
I'm in trouble when it comes to @-patterns: is xs@(x:_) acceptable?
For non-integral numbers, I often use x, y.

 I think most of the Haskell code I've ever seen that *wasn't* written by
 me follow these conventions pretty closely.  But the strange thing is...I
 haven't found a prominent place on, e.g., the Haskell home page where this
 is spelled out. (Please tell me if I'm missing anything obvious.) In a
 way, I guess this is trivial, but I know from hard experience it can often
 take a long time to become completely aware of trivial things.

I've seen the (x:xs) (or whatever letter you want, BTW I'd use (f:fs)
for a list of functions) convention written somewhere. Most of the
rest is what is usually used in mathematics or is done in any computer 
language (such as c for Char).
Yes, a list of these things might be helpful.


Christian Sievers





Re: Church numerals in Haskell

1999-06-03 Thread Christian Sievers

Jerzy Karczmarczuk wrote:

 6. Subtraction. Largo.
According to some folklore Church himself thought for some time
that it is not possible to define the subtraction using pure
lambdas. 
In fact it is possible to subtract Church numerals (but never 
getting negative numbers, of course) The following solution is
silly, but please find a *really* better one...
 
First the incrementation:   inc n s z =  n s (s z)
(You may use it also to define the addition.)
 
Then the iteration defining the decrement
  dec n = d zer where
 zer s z = z
 v = n s z  -- global constants
 d m = let h = inc m
   in if h s z == v then m else d (inc m)
and the subtraction is the iterated decrement. Its complexity
is really bad (n^2).

Compared to using equality, I think the following is really better:

dec n = fst (n (\(_,b)-(b,inc b)) (zer,zer))   where zer s z = z

Of course, you wouldn't really use built-in pairing, would you?


Christian Sievers





RE: non-linear patterns

1999-05-06 Thread Christian Sievers

Frank A. Christoph gave examples for unintended non-linear patterns,
among them:

 Or, even more more common:
 
   f (x@(x,y)) = ... --- oops!

If I don't oversee something obvious, this just would fail to
type-check, so this shouldn't be a problem.


Christian Sievers





Re: Haskell-98 Quiz

1999-04-23 Thread Christian Sievers

Magnus Carlsson wrote:

 Here are some questions for the Haskell-98 enthusiasts.

I'm not sure if I'm a Haskell-98 enthusiast, I still call myself 
a Haskell enthusiast.

 1. Why is the following declaration group illegal?
 
   f :: String
   f = g 1 ++ g True
 
   g :: Show a = a - String
   g x = fst (show x, show f)

I don't see why it should be illegal, but then nor does Hugs 98.
It is happy with this definition and gives "1True" for f.
So if you found a subtle strange thing in Haskell 98, you also found a 
bug in Hugs.


Christian Sievers






Re: Modifying the monomorphism restriction

1999-02-24 Thread Christian Sievers

John Hughes wrote:

 Everybody agrees the monomorphism restriction is a pain:

Hmm well, it's really not a nice thing.

 Some suggest that it is enough for compilers to issue a warning when using
 call-by-name. I disagree strongly. Such a warning may alert the programmer
 at the time the overloaded definition is compiled. But programmers need to
 understand programs at other times also. The person reading through the code
 of a library, for example, trying to understand why a program using that
 library is so slow or uses so much memory, will not be helped by warnings
 issued when the library was compiled. The distinction between call-by-need
 and call-by-name is vital for understanding programs operationally, and it
 should be visible in the source.

In a library I'd really expect to see a big comment when such a thing
happens. 

 So, let's make it visible, in the simplest possible way. Let there be TWO
 forms of binding: x = e, and x := e (say). A binding of the form `x = e' is
 interpreted using call-by-name, and may of course be overloaded: it makes `x'
 and `e' exactly equivalent. A binding of the form `x := e' is interpreted
 using call-by-need, and is monomorphic; `x' behaves as though it were
 lambda-bound. Now, for example,
 
   pi = 4*arcsin 1
 
 is an overloaded definition which (visibly) risks duplicated computation,
 while
 
   pi := 4*arcsin 1
 
 is a monomorphic definition at a particular instance which (visibly) does not.

But which instance? In this case the default mechanism can give the
answer, but in general, you would have to give a type unless `e'
already has a monotype. So you could use `x:=e' without a signature
exactly when you now could use `x=e' without one. 


 Advantages of this idea over the existing MR:
 
 * Monomorphism is decoupled from the syntactic form of the definition. There
   is no need to `eta-convert' definitions to get them into a form that the MR
   does not apply to.

The difference between `x=e' and `x:=e' is surely a syntactic one,
though arguably one that is easier to justify.

 * Monomorphism is decoupled from overloading. With this proposal, x := e is
   always a monomorphic definition, whether the type of e is
   overloaded or not.

Again: how can this be?

   Thus small changes to e cannot suddenly bring the MR into effect, perhaps
   invalidating many uses of x.
 
 * Monomorphism is decoupled from type inference. One may leave the type of 
   a variable to be inferred regardless of whether it is bound by name or by
   need.
 
 Disadvantages:
 
 * Requires another reserved symbol.

 * When converting Haskell 1.x to Haskell 2, many := would need to be inserted.
   Failure to do so could make programs much less efficient. An (optional)
   compiler warning could help here.

I don't see this. Or do you want to always recalculate any value
defined with `=' instead of `:=' ?
 
 An alternative design would be to use := to indicate polymorphism/overloading
 in pattern bindings, but retain = for polymorphic function bindings. That
 would make conversion from Haskell 1 to Haskell 2 simpler (one would simply
 replace = by := in pattern bindings with an overloaded type signature), but is
 an unattractively inconsistent design.


I don't like this idea (yet?), and would prefer the compiler-warning
version, or even keep the MR - we could make our editors smarter and
let them add the types if they change too often or are just too weird
for us, rather than introduce new syntax only in order to be able to
leave them out.


Christian Sievers





Re: Haskell 98 final stuff

1999-01-29 Thread Christian Sievers

Simon writes:

 2.  The data and type constructors 
   (), (,), (,,), etc
   []
   (-)
 are all regarded as "syntax", not as identifiers.  They always mean
 their standard meaning (tuples, empty list or list type constructor).
 [No change here.]
 
 The question is: what about the list constructor ":".  In principle
 we could regard it as an ordinary identifier, and therefore allow someone
 to redefine it... but
  [there are problems.]
 
 I have concluded that it is simpler to treat ":" as syntax, exactly
 uniformly with the others.  It always means list construction, and
 it cannot be hidden or redefined.

 li Section 2.4. Clarify that tt:/tt is reserved solely for Haskell
 list construction.

What does this mean? Will there only be a remark, or will the syntax
be changed? The other constructors are explicitely handled by the
syntax, so I guess this should be done in this case also. Doing that
'exactly uniformly' would mean productions for expressions e:e,
patterns (p:p) and the constructor (:). But we surely don't want to
loose the sections (e:) and (:e).
Please don't forget them! 


All the best,
Christian Sievers






Re: Two prelude/library matters

1998-11-06 Thread Christian Sievers

 1.  The Show class
 ~~
[...]
   class  Show a  where
   showsPrec :: Int - a - ShowS
   show:: a - String  -- NEW
   showList  :: [a] - ShowS
 
   showsPrec _ x s = show x ++ s
   show x  = showsPrec 0 x ""
   showList= ...existing default declaration

This gives one more example of what I always wanted to suggest:
The documentation of a class should clearly state which the minimal
sets of definitions are that one has to give, rather than let the
reader figure this out from the code. Default class definitions are
very convenient, but these recursive ones that look like everything is 
already defined are a bit mysterious. I agree one might like to define 
one member function, another, or both, but tell them what to do at
least. This change looks very good.

The default for (==) however seems odd to me. Someone could like to
define (==) alone or both (==) and (/=), but it seems strange to me to 
only define (/=). Or do you just want to give all expressible
relations?

And while you're still doing non-hurting class definition changes, let 
me repeat this: please let succ and pred be Enum class members.


Christian Sievers





RE: MonadZero (concluded)

1998-11-06 Thread Christian Sievers

  Yes, nuke MonadPlus. For Haskell 2 we can put these things in a
  wonderful Monad library.
 
 I had thought that too many functions depend on MonadZero/Plus,
 but actually, it's the following:
 
 filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
 guard   :: MonadZero m = Bool - m ()
 mfilter :: MonadZero m = (a - Bool) - m a - m a
 concatM :: MonadPlus m = [m a] - m a
 
 These would all vanish, along with MonadZero/Plus.
 The Monad library itself doesn't mention MonadZero/Plus, as it happens.
 
 Phil's proposal:
   delete class MonadZero, MonadPlus
   delete filterM, guard, mfilter, concatM
 
 This is ok by me.  Does anyone object?

In fact I don't know these functions, but when they were in the
Prelude can they be less important than those in the Monad
library? Why don't we move the classes and functions into a wonderful
Monad library already now for Haskell 98?

And, BTW, the library report defines types for zeroOrMore and
oneOrMore, which both are  (MonadPlus m) = m a - m [a],
but doesn't mention them later.


Christian Sievers





Re: MonadZero

1998-11-05 Thread Christian Sievers

Hi, it seems to be much too late after all the discussion but among
the alternatives was

   3.  Make tuples special, so that g would be in Monad, but
   if we had a user-defined single-constructor type instead
   then it would be in MonadZero

about which was said

 (3) seems dreadful.

I'm not so sure. If we don't call it make them special, but let them
be unlifted products (and hence irrefutable patterns), how would that
sound? Why are they lifted, anyway? If it's only so that we can say
tuples are nothing but syntactic sugar for something one might
otherwise declare as a data definition oneself, I'd be happy to give
that away. And I never liked the lifting of single-constructor types,
so I don't use them. After all, there is still newtype.

I also like (5) [status quo].
I don't feel happy with the proposed changings in the definition of
Monad, but I can't give good (let alone new) reasons for that.


Christian Sievers





let succ be an Enum class member

1998-05-12 Thread Christian Sievers

Hello, this is about a change in the prelude I'd like to suggest.

The following is obviously not what one would expect:

  Prelude succ 100::Integer

  Program error: {primIntegerToInt 100}


However, with the prelude defining succ to be

  succ,:: Enum a = a - a
  succ =  toEnum . (+1) . fromEnum

we can't hope for anything better.

My suggestion is to make succ a member function of class Enum, with
the old definition as default, so that the instance Enum Integer
can define it to be simply (+1).

Another example is
  data Nat = Zero | Succ Nat
where succ=Succ is not only more natural, but also much more
efficient.

Of course the same holds for pred.

What do you think?
Are there any drawbacks?
Could it be like this in standard haskell?


Christian Sievers





Re: what's wrong with instance C a = D a. Reply

1997-08-25 Thread Christian Sievers

I wrote:

   Sergey Mechveliani wrote:

   :   As to   `instance D a',   
   :   it is not a loss. Because `instance D a' is the same as  
   :   `class D a' - supplied with the default definition. For example,
   :   the illegal declaration pair
   :
   : classC a = D a  where  d :: a - a
   :
   : instance C a = D a  where  d = definition
   :
   :
   :   can be replaced with the legal and simpler declaration
   :
   : class C a = D a  where  d :: a - a
   :  d = definition
   :
   [...]
   You're equivalence is correct ...

Buzzz. No, it's not. It does not actually give any instance of D.
You have to declare all of them seperately, and you would rather want
to just say instance C a = D a but you can't.
It's much like the Textual example.

Christian Sievers





Re: how about main :: IO Int

1997-08-25 Thread Christian Sievers

Thank you for pointing me to the System library. However, while I was
indeed implying that there is no way of returning an exit code, my main
question was which type main should have. You seem not to like IO Int
(one even for several reasons ;-) but it still looks quite natural to me. 

Christian Sievers





Re: what's wrong with instance C a = D a. Reply

1997-08-22 Thread Christian Sievers

Sergey Mechveliani wrote:

:   As to   `instance D a',   
:   it is not a loss. Because `instance D a' is the same as  
:   `class D a' - supplied with the default definition. For example,
:   the illegal declaration pair
:
:classC a = D a  where  d :: a - a
:
:instance C a = D a  where  d = definition
:
:
:   can be replaced with the legal and simpler declaration
:
:class C a = D a  where  d :: a - a
: d = definition
:
:   Correct me please, if this is a mistake, I am not much of an 
:   expert in Haskell (though keep on programming for two years!)


You may have learned from my other posting that I am also not an
expert :-) -- quite enthusiastic though.
You're equivalence is correct (as much as an illegal decl. can be
equiv. to a legal one), but not general enough for me. I didn't want
the class D to be a subclass of C. Maybe I should give the example
that I have abstracted away from. It's a simple variation of an example
from Mark Jones, given in "Fun. Prog. with overloading and
higher-order polymorphism" in 1st Int. Spring School on
Adv. Fun. Prog. Techniques, LNCS 925. There he defines

 class Dual a  where  dual :: a - a

(dual is expected to satisfy   dual . dual = id)

 instance Dual Bool  where   dual = not
 instance (Dual a, Dual b) = Dual (a-b)
  where dual f = dual . f . dual
 instance (Dual a) = Dual [a]  where  dual = reverse . map dual

and has also

  instance Dual Int   where   dual = negate

which I tried to replace by the obvious generalisation

? instance (Num a) = Dual a   where   dual = negate

However, this is not legal in haskell (no problem for gofer).
While this was just experimenting, there might be other examples where
one would like to be able to have instance decls like this. 

The report suggests using 
  class  (Read a, Show a) = Textual a
for which one would have to give explicit instance declarations as
well. If I want to give it for all possible instances, I would want
to write
  instance (Read a, Show a) = Textual a
but I can't.


:   As to instance ... = C (a  ,a)  where ..., 
: ...  = C (Int,a)  where ..., 
:   and such,  
:   they might express a very meaningful mathematical sense, these
:   constructions are highly desirable. 

Actually, these worry me less. If they are meaningful, maybe they
should be given meaningful names. For example, the one you left out,
namely [[a]], if it has some special meaning, which [a] has not, then
there is something really special about it, and it should be called
Matrix a  or so. Though less obvious, I think the same holds for the
other examples. Still, I'd prefer if they were allowed...


Christian Sievers





what's wrong with instance C a = D a

1997-08-21 Thread Christian Sievers

The report says explicit that instance declarations like
instance C (a,a) where ...,  or for (Int,a) or for [[a]] are not
allowed. I tried to understand this by thinking these types are too
complex, but I had to learn that a type may also be too simple,
i.e. just writinginstance D ais not allowed either.
I had to look at the grammar to believe it. At least with a context as
in the subject line, this should be useful. However, I don't suggest
(only) this should be added, I rather hope that the people arguing for
multi parameter type classes will make it (if not in Standard Haskell,
then maybe in Curry:).
I now only would like to know why this design decission was made,
are there any problems with the instance declarations I have in mind?

Christian Sievers






buffered output; :s -p%s%s%s

1997-05-06 Thread Christian Sievers

Hello,

I noticed two things which I think might be called bugs, at least I am
near doing so:

The first thing really annoys me:
If you input something like

   [0,x] where x=x

you get no output at all before you interupt.
I think the output is buffered, and I don't like it.
This is worse in less strange examples like doing a slow calculation
of a list, e.g. calculating perfect numbers by filtering all numbers.
If you really want to buffer output even to stdout, please consider
flushing it frequently.

The other thing is less import and more like a bug, after all it lets
you crash hugs quite easily. (I really guess you know it.) Just type 

:s -p"%s%s%s"

(you may need more %s's -- three were always enough for me -- and can
of course also use %i or whatever you like).
The reason is obviosly the way the prompt is enabled to tell the last
loded module (a feature I don't like as a default anyway), so some
checking of the string given to the p-option should be done.
Perhaps more complex things could be done in order to cleanly allow
even more prompt tricks.
I considered doing it myself, but I really can't do it this month.

I don't think it matters, but I tried this with Linux and SunOS,
and the hugs version calls itself 970410.

Christian Sievers