List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften
Hello,

Recently, I came accross this
expression:
[ x + y | x - xs | y - ys ]

As far as I can see (Haskell Report),
this is not allowed by the haskell 98
standard. So I assume it to be an ex-
tension. Where can I find information
about this?

Thanks,

Rijk

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



Re: List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften


* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]:

 Recently, I came accross this expression:
 [ x + y | x - xs | y - ys ]
^
Put a comma ',' here.


That's something totally different. Two examples:
1. Comma
  [ x + y | x - [1,2], y - [3,4] ]
= [4,5,5,6]

2. Bar
  [ x + y | x - [1,2] | y - [3,4] ]
= [ x + y | (x,y) - zip [1,2] [3,4] ]
= zipWith (+) [1,2] [3,4]
= [4,6]

The first is according to the standard. No problems so far.
However, I couldn't find a description of the semantics of
the second (and it is clearly non-standard), though I think
the semantics given above using zip and zipWith are correct.

Rijk

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



RE: 3 `\x y - x + y` 4 `\x y - x + y` 5: Wrong version pasted

2002-08-22 Thread Rijk J. C. van Haaften

I pasted the wrong version into the mail.
This is the final one:

module InfixFunction where

infixl 0 $-
infixr 0 $+

-- for left-associative functions
($) :: a - (a - b) - b
($) x f = f x

-- for right-associative functions
($) :: a - (a - b) - b
($) x f = f x

example1 :: Int
example1 =
-- 3`\x y - x + y`  4
   3 $ (\y x - x + y)  4

example2 :: Int
example2 =
-- 1`\x y - x + y` 2`\x y - x` 3
   1 $ (\y x - x + y) 2 $ (\y x - x + y) 3


Rijk-Jan van Haaften

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



Re: Binary search tree

2002-04-29 Thread Rijk J. C. van Haaften


Hi everybody,

I studied haskell this semester at the university and I was required to
implement a binary search tree in haskell.
I would appreciate if anyone could send me an example code of this data
structure.

Just read a standard textbook. Some useful course notes
by Jeroen Fokker are available online at
http://www.cs.uu.nl/people/jeroen/courses/fp-eng.pdf
Enough to solve your problem.

Rijk-Jan van Haaften

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



Re: ANNOUNCE: Object I/O released

2002-04-09 Thread Rijk J. C. van Haaften


The quick reference still gives problems.

I managed to download the quick reference.
Get it at
http://www.students.cs.uu.nl/people/rjchaaft/ObjectIO/objectio-ref.zip

This is a very temporarily available service,
so if anyone has a suitable server (again, cvs.haskell.org?),
please take over hosting the file.

Rijk-Jan

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



Re: ANNOUNCE: Object I/O released

2002-04-08 Thread Rijk J. C. van Haaften

Hello all,

Peter Achten and Arjan van IJzendoorn wrote:
I ... unfortunately could not open the .zip files

and Peter asked
Could you check the formats of these files?

After having tried to download the file a few times, I believe
the problem is not in the zip file format, but download failure.
(Until now, I didn't manage to download more than 3 MB, though
the file should be 4 MB.)

Krasimir, can you please put the file on another server (maybe
the cvs.haskell.org maintainers are willing to store the file;
ask Jeff Lewis, [EMAIL PROTECTED])?

Regards,

Rijk-Jan

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



Re: Typo: Hugs Bug ! it was +

2002-03-22 Thread Rijk J. C. van Haaften

Ahn Ki-yung wrote:
Prelude f 1 where f x = x : f x
[1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,
,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,
,1,1,{Interrupted!}

Prelude f 1 where f x = x + f x

-- Immediate (!) crash

Indeed, I could reproduce this on my computer
(Win2000; Hugs Dec 2001 of last week).

Rijk-Jan van Haaften

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



Re: Hugs Bug !

2002-03-21 Thread Rijk J. C. van Haaften


but in windows 2000

Then suddnly interpreter fails and
the red (X) popup window pops up.

hugs.exe - application programm error

 unknown software exception (0xc000fd) ... blabla

Are you sure you have the very very very latest download?
There have been some undocumented updates of the December
2001 release of Hugs.

Download the very latest release and try it again.

I tried you expression on Win2000, with Hugs Dec 2001,
downloaded last week, and it runs in constant space
for an unlimited time.

Rijk-Jan

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



Rectification Hugs bug

2002-03-07 Thread Rijk J. C. van Haaften

Dear all, 

After intensive investication of several people here at
Utrecht University, these are the results
 1. The very latest Hugs version doesn't have the bug
 2. All before-december-2001 versions don't have the bug
 
I were using a version downloaded some weeks ago. After
installing the current distribution, the problems disappeared

Therefore, I suspect there have been one or more
bug-fix updates after December 2001, fixing this problem.
However, I couldn't find that documented on the Hugs site.

Can anyone confirm such an update? Where can I find last-
minute distribution information?

Thanks,

Rijk-Jan 

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



Rectification Hugs bug

2002-03-07 Thread Rijk J. C. van Haaften

Dear all,

After intensive investication of several people
at Utrecht University, these are the results:
1. The very latest Hugs version doesn't have the bug
2. All before-december-2001 versions don't have the bug

I were using a version downloaded some weeks ago.
After installing the current distribution, the problems
disappeared.

Therefore, I suspect there have been one or more
bug-fix updates after December 2001, fixing this problem.
However, I couldn't find that documented on the Hugs site.

Can anyone confirm such an update? Where can I find
last-minute distribution information?

Thanks,

Rijk-Jan

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



Bug in Hugs Dec 2001: type inferencer incorrect!

2002-03-06 Thread Rijk J. C. van Haaften

Hello everybody,

Although I didn't manage to reproduce the
bug with a minimal example, I think it is
still important enough to tell you (and
especially the Hugs writers and maintainers).

Yesterday evening, I tried to add some correct
(!) code (by-hand-verifyable; by GHC accepted;
just using plain Haskell 98) to one of the
projects I'm working on.

Hugs however said this:
Type checking
ERROR TypeInferDecls.hs:102 - Type error in application
*** Expression : checkedUnify (snd newTyEnv) inferredHpPtr explicitHpPtr (\t1 t2 
ue - ([l],ExplicitError n t1 t2 ue))
*** Term   : checkedUnify
*** Type   : NonGenerics - HpPtr - HpPtr - ErrorFunction - TI Error ()
*** Does not match : a - b - c - d - e
*** Because: types do not match

I've read this ten times, checked my code
looking whether I were doing strange things,
but I can only conclude:
This is, even without a minimal example,
clearly a bug: the types do match.

Moreover, the bug is reported about a completely
different part of the file (relative to the location
I edited), in code almost unrelated to the code
I added (about line 300).

I have explicit types everywhere in that file,
so if it were wrong, the error should be
reported about line 300. So the reporting-place
is wrong (but I don't expect Hugs to report
good error-placement).

Though I didn't manage to write a minimal
example, I hope our Hugs experts are able
to find the bug soon.

As a last point: the file is rather big:
726 lines of code, 27KB.

Rijk-Jan van Haaften


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



Bug in Hugs Dec 2001: type inferencer incorrect!

2002-03-06 Thread Rijk J. C. van Haaften

Hello everybody,

Although I didn't manage to reproduce the
bug with a minimal example, I think it is
still important enough to tell you (and
especially the Hugs writers and maintainers).

Yesterday evening, I tried to add some correct
(!) code (by-hand-verifyable; by GHC accepted;
just using plain Haskell 98) to one of the
projects I'm working on.

Hugs however said this:
Type checking
ERROR TypeInferDecls.hs:102 - Type error in application
*** Expression : checkedUnify (snd newTyEnv) inferredHpPtr explicitHpPtr (\t1 t2 
ue - ([l],ExplicitError n t1 t2 ue))
*** Term   : checkedUnify
*** Type   : NonGenerics - HpPtr - HpPtr - ErrorFunction - TI Error ()
*** Does not match : a - b - c - d - e
*** Because: types do not match

I've read this ten times, checked my code
looking whether I were doing strange things,
but I can only conclude:
This is, even without a minimal example,
clearly a bug: the types do match.

Moreover, the bug is reported about a completely
different part of the file (relative to the location
I edited), in code almost unrelated to the code
I added (about line 300).

I have explicit types everywhere in that file,
so if it were wrong, the error should be
reported about line 300. So the reporting-place
is wrong (but I don't expect Hugs to report
good error-placement).

Though I didn't manage to write a minimal
example, I hope our Hugs experts are able
to find the bug soon.

As a last point: the file is rather big:
726 lines of code, 27KB.

Rijk-Jan van Haaften


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



Why is this function type-correct

2002-03-04 Thread Rijk J. C. van Haaften

Hello,

Recently, I wrote a function similar to

x :: a
x = x 42

which is type-correct (Hugs, Ghc, THIH).
Still, from the expression it is clear
that the type shoud have a function type.
The definition

x :: a - b
x = x 42

is equally well accepted, though I can't
see why this type would be correct. (I'd
expect it to be too general.)

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



Why is this function type-correct

2002-03-04 Thread Rijk J. C. van Haaften

Hello,

Recently, I wrote a function similar to

x :: a
x = x 42

which is type-correct (Hugs, Ghc, THIH).
Still, from the expression it is clear
that the type shoud have a function type.
The definition

x :: a - b
x = x 42

is equally well accepted, though I can't
see why this type would be correct. (I'd
expect it to be too general.)

For what reasons are these types considered
correct?

Thanks,

Rijk-Jan

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



Re: Ground Up

2002-02-28 Thread Rijk J. C. van Haaften

Jerry wrote

However, my problems are:
* I still don't understand most of the codes I found, like the various
   haskell libraries
Practice is the only answer to this problem, as Keith Wansbrough says.

* I still have no clue of most (ok, almost all) of what is being
   discussed in this mailing list
Though I am a CS student, being highly interested in Haskell and
practising a lot, I didn't understand most of the discussions on
this mailing list.
I started understanding them only after I got involved in implementing
a Haskell compiler.
Therefore, don't worry about this point. A haskell-user doesn't
need to know the details of the haskell compiler ins and outs.

Rijk-Jan van Haaften

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



Re: Help

2002-02-25 Thread Rijk J. C. van Haaften

You probably want to do something like this:

main =
 do {
 contents - input twoboxes.dat
 return (control (parser contents))
 }

At 11:53 25-02-02 -0300, Juan M. Duran wrote:
Hi, I'm writting a small parser in Haskell and, when it is all done, I get
the following problem: Type Binding.
The thing is, I have 3 main functions:
1) Read the file, its type is: [Char] -IO [Char] (see InputOutput.hs)
2) Parse a string (using words and readDec), its type is: Integral a =
[Char] - [a] (see Parse.hs)
3) Parse a list of integer, its type is: [Float] - [[Float]]
(Functions.hs)

Now the problem is that I cannot run the first function, then use its
results as an input of the second function and, finally, its results as
the input of the third function.

How can I fix this without modifing all my functions because they,
independly, works fine.

Juan

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



ANNOUNCE: Haskell support for JCreator update

2002-02-13 Thread Rijk J . C . van Haaften

Dear reader,

I'm pleased to announce the availability of a release of the Haskell module 
for JCreator. You can get it, as usual, at
http://www.students.cs.uu.nl/people/rjchaaft/JCreator

The previous update lacks the documentation tool, and is quite restrictive 
concerning the location of Hugs, the Haskell Graphics Library and JCreator.

This update reintroduces the documentation tool. The problems that were 
reported about the tool (incompatibilities between windows versions) are 
fixed (hopefully).
The html version of Bernie Pope's Tour of the Haskell Prelude, made by 
Arjan van IJzendoorn is included as well (under the same documentation tool).
The requirement that Hugs, the GraphicsLib and JCreator are installed in 
certain directories is removed, thanks to the use of a new installer.

Enjoy,

Rijk-Jan van Haaften

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



Re: Specifying Kinds of Types

2002-02-08 Thread Rijk J . C . van Haaften

Ashley Yakeley wrote:
I'd like to be able to declare the kinds of new types and synonyms,
because sometimes Haskell can't infer them. For instance:

 data CMap0 p q = MkCMap0;

Without evidence, Haskell assumes that p and q have kind '*' (as per sec.
4.6), and therefore CMap0 has kind '* - * - *'. Actually, I wanted p
and q to both have kind '* - *', giving CMap0 kind '(* - *) - (* - *)
- *'.
...
It's not currently possible to specify kinds, is it?

It is possible using a trick due to John Hughes. In
 Proceedings of the 1999 Haskell Workshop,
he wrote in his article
 Restricted Data Types in Haskell
this note:

  3 There is one unpleasant hack in the figure: The constructor Unused 
in the
 data type definition for Set. It is there purely in order to force the 
compiler
 to assign the parameter cxt the correct kind: without it, cxt does not 
appear
 at all in the right hand side of the definition, and is therefore 
assigned the
 (incorrect) kind *. The application cxt a forces the correct kind * - 
* to be
 assigned, and embedding it in the type cxt a - () prevents the type 
of the
 context from interfering with the derivation of a Show instance.

The figure mentioned contains

 data Set cxt a = Set [a] | Unused (cxt a - ()) deriving Show

You can follow the example of John, writing

data CMap0 p q = MkCMap0 | Unused (p a - ()) (q a - ());

(I think I'm correctly applying the trick, but other
Proceedings-readers will correct me if I'm wrong.)

As John writes, this is a hack, but we have no
other choice.

Rijk-Jan van Haaften

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



Re: Problem with 'nested' pattern matching

2002-02-01 Thread Rijk J . C . van Haaften

carlos wrote:
Hello. 

I'm having
some trouble trying to understand exactly what's behind the rule for
pattern-matching with data constructors. The code I'm having trouble with
is similar to this: 

f (C p1 p2 (C2 p3 p4)) = ... 
f _ = False 

What happens is if f is called with (C p1 p2 (NOT_C2 ...)), I get a
program error, and not False.
I tried this in Hugs:

data Test
 = C Bool Bool Test
 | C2 Bool Bool
 | NOT_C2 Int

f :: Test - Bool
f (C p1 p2 (C2 p3 p4)) = (p1  p3) || (p2  p4)
f _ = False 

evaluating f (C True False (NOT_C2 25)) gives False as expected.
Which compiler/interpreter do you use? Which version?

Actually I can't imagine a bug of this kind in any of the mainstream
compilers (GHC, HBC, NHC and NHC) and interpreters (Hugs, GHCi, and HBI),
though on this computer I only can check hugs.

Regards,

Rijk-Jan van Haaften



RE: n+k patterns

2002-01-30 Thread Rijk J. C. van Haaften

At 03:27 30-01-02 -0800, Simon Peyton-Jones wrote:
| hbc is on the Integral side, if that counts. :-)
| Just because ghc doesn't follow the spec isn't a good reason
| to change the spec. :-)

I absolutely didn't say that!  All I'm saying is

* Two of the four impls have to change regardless
* The change is non-de-stabilising on the rest of the report
* So we should think what the best answer is

I argued that (Num a, Ord a) makes most sense to me.
You argued that (Integral a) was a conscious choice (something I
don't remember but I'm sure you're right), and is the right one anyway.

I'd be interested to know what others think.  If there's any doubt,
we'll stay with Integral.

Personally I vote for keeping Integral. The strongest reason
for my choice is that if we want to be sure the pattern is
really correct, we need a bijection.
For Integral, we have + and - to form one, but we can't construct
one for Float and Double, though by this change they would be allowed
in the pattern.

Rijk-Jan van Haaften


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