Hi,
Take a look at the following program, making use of
derivable type classes.
>>>
module Bug where
import Data.Generics
class Foo a where
foo :: a -> Int
foo{| Unit |}_ = 1
foo{| a :*: b |} _ = 2
foo{| a :+: b |} _ = 3
instance Foo [a]
<<<
GHC 6.2.2 produces the following error
Hi,
Compiling the following program (Bug.hs):
>>>
module Main where
import System.Console.Readline
main =
do ms <- readline "Hi> "
print ms
<<<
Using GHC 6.2.2 on Windows XP, using the command line:
ghc --make Bug -o bug
Produces the following message:
>>>
Chasing modules from: Bug
| system("ld -r -x -o " ++ ghci_lib_file ++
| " --whole-archive " ++ batch_lib_file)
It works with gld however! Maybe configure should insist
on gld being there.
/K
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.
I am using ghc-pkg on SunOS4 and get the following behavior
when using 'ghc-pkg -g':
>>>
ld: illegal option -- x
ld: illegal option -- -
ld: illegal option -- w
ld: illegal option -- x
ld: illegal option -- -
ld: illegal option -- w
<<<
My guess is that it is trying to build a .o file from a .a
Dear Simon, Simon and Sigbjorn,
I have finnaly managed to go through a complete "make"
session without any errors! (There is a caveat: see end of
mail).
Some comments: In the end, it worked out-of-the-box. But it
only did that after I had installed and reinstalled out of
the necessary tools and
Hi,
This is a bug which has been in GHCi from the beginning.
Bug
===
GHCi interprets a module while the compiled version is
present and up-to-date.
Details
===
When I (for example) have the following module structure:
module A where
...
module B where
import A
...
The f
Hi,
Given a file "test" of size 2342.
The program "Bug.hs" behaves correctly (the result is
"(2048,384)"), but when uncommenting the seemingly innocent
line, the program behaves incorrectly (result is
"(2048,2048)"), and the buffer is filled with garbage.
main =
do han <- openFile "test" Read
FormParse.hs", I get the impossible error.
/Koen.
{-# OPTIONS -fglasgow-exts #-}
{-
module Parsek
---
Author: Koen Claessen
Date: 2001-01-27
Compliance: hugs -98 (needs "forall" on types)
Licence:
Hi,
I discovered two bugs in GHCi. I am using GHC5.02 on
Linux.
The first bug has been there for some time now. If I start
GHCi with a module `A.hs', which either does not exist
itself, or which includes modules that not exist, then GHCi
terminates with an error message. This is rather strange
Hi,
I discovered a minor cosmetic bug today. After my
undescribable hapiness about the fact that GHCi now has the
":i" command, I started playing around, and discovered the
following ugly output:
Prelude> :i []
-- [] is a data constructor
[] :: forall t_12. [t_12]
-- [] is a type constr
Hi,
I have two bug reports related to using the Concurrent
module in GHCi (I am running 5.02 on Solaris).
1)
I get the following behavior:
Main> forkIO (print "1")
Main> forkIO (print "2" >> print "3")
"1"
Main> print "4"
"2"
"4"
"3"
It seems that GHCi returns to the prompt when
Hi,
I noticed a difference in behavior between running:
> ghci -package utils
And:
> ghci
...
Prelude> :set -package utils
On our system, the first one works (it finds all the right
dynamic libraries and stuff), but the second one doesn't (it
cannot find libreadline.so, and other dyna
Hi,
The function "mkPortNumber" is gone from the Socket library:
Prelude> :t Socket.mkPortNumber
:1: Variable not in scope: `Socket.mkPortNumber'
Though it is still mentioned in the documentation for
GHC-5.02.
/Koen.
___
Glasgow-haskell-bugs m
ing this as a bug, because:
* either the FFI should work (but it doesn't)
* or it does not work (but GHC panics anyway)
In either case this is a bug...
/Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 54
Hi,
When I load tha Yahu package [1] in GHCi 5.02 on a SParc
running Solaris, I get the following message:
>>>
scooter> bin/yahu.new Resources/YahuNew/Examples/Balls.hs
___ ___ _
/ _ \ /\ /\/ __(_)
/ /_\// /_/ / / | | GHC Interactive, version 5.02,
for Haskell 98.
/ /_\\/ __
| I'm not sure it's a bug - Haskell 98 doesn't require
| that the TimeDiff value returned from diffClockTimes
| is normalised in any way, and it can't be done in
| general of course because months and years have
| different numbers of days, even minutes have different
| numbers of seconds i
nd a
tdMin field of 0. I guess this is a bug.
I am running ghc-5.00.2 on Linux.
/Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Go
e net -c Apa.hs", I get:
Apa.hs:6:
No instance for `Eq Socket'
arising from use of `==' at Apa.hs:6
in the definition of function `foo': x == x
/Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424
Hi,
I discovered some mistakes in Chapter 7.17, "Generics", in
the GHC documentation on the web.
In 7.17.2, it says:
"{|" and "{|"
This should be "{|" and "|}" of course.
In 7.12.3, there is a little code fragment, that looks like
this:
class Foo a where
op1 :: a -> Bool
tk.so
> ghci primtk.so Yahu.hs
...
But then, GHCi complains about "primtk.so", it does not
recognize it as a dynamic object file. (Which it strange,
because there is an error message that identifies ".so"
files as valid arguments to GHCi...)
/Koen.
--
Koen Claess
to figure out where its other
| bits and pieces are, though.
But one could *add* one's own local package.conf file, in
addition to the global one.
/Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 mail
Hi,
I wonder if it is possible to use one's own "packages.conf"
file, so that users can make their own packages?
It would be nice if there were a flag to ghc and to ghc-pkg
that also allowes using a local package file.
/Koen.
___
Glasgow-haskell-bug
Hi,
If I load the following module:
module Apa where
import ST
apa = newSTRef () >> return ()
into "ghci -package lang", and I ask for the type of "apa",
the following happens:
Apa> :t apa
ST () ()
This is obviously wrong, it should be (as "hugs -98" says):
Apa> :t apa
apa :: S
o "system", and that I press control-C during the
evaluation of the system call.
I do not think it makes much sense for me to send you my
code, since:
1. This bug occurs with a lot of different code I have.
2. The particular code I have is HUGE.
We are running Linux.
/Koen.
-
Hi there,
I came across a VERY STRANGE bug in GHCi. It is difficult to
pin down.
I send a couple of modules. Running "main" in the module
called Toggle, generates a file called "system.galf". This
is wrong!
At line 14, it says "bool(true).". To generate this, it must
use definitions from the mo
Which is completely useless (you *need* binary split if you
want to avoid state-threading).
Maybe GHC has the same problem?
Regards,
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
--
The following program gives errors with GHC-4.01:
data Def f = String := f String
I had to put parantheses around "f String":
data Def f = String := (f String)
I think this is a bug; Hugs and HBC accept it.
Koen.
--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmer
-: secretary
[0.398, 0.386, 0.376, 0.353, 0.363]
<<<
Or even:
>>>
Hugs> main
[0.366, 0.369, 0.383, 0.383, 0.379]
<<<
I am trying to find out if it is because of the random numbers, or because
of the use of -O. But these programs take ages to run...
Regards,
Koen.
--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.
ard.h" not
begin there.
And indeed, that file does not seem to be part of the
distribution.
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
-
Chalmers University of
ards,
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden
Okay, I started compiling the fresh H/Direct.
Here is the message I got:
panic! (the `impossible' happened):
Check.check': Not implemented :-(
Please report it as a compiler bug to [EMAIL PROTECTED]
Hm
Koen.
--
Koen Claessen http://www.cs.chalmer
nd the file HDirect.h anywhere in the distribution...
So I can't compile my c-code...
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
-
Chalmers University of Techno
llowing piece of code:
module Utils
( <...>
, (#)
<...>
)
(I don't know if this is a bug in -fglasgow-exts).
In any case, the H/Direct makefile should automatically
switch on the flag for "forall". How does one do that?
Thanks,
Koen
why a makefile has to be so complicated!
:-)
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424 e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden
Koen Claessen, I, wrote:
| [hdirect-0.15] -: make boot
| make: Fatal error in reader: ./mk/boilerplate.mk, line 13: Unexpected
| end of line seen
I should have used "gmake" of course...
Koen.
--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424
Koen Claessen wrote:
| Utils.lhs:22: parse error on input `(#'
I fixed this error by saying: "( # )" instead of "(#)" in Utils.lhs.
"make" works fine now.
But now I have another problem, after typeing "make lib":
PointerPrim.hs:31: unknown
36 matches
Mail list logo