Readline on Windows?

2004-11-22 Thread Koen Claessen
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
Compiling Main ( Bug.hs, Bug.o )
Linking ...
c:/ghc/ghc-6.2.2/libHSreadline.a(Readline__96.o)(.text+0xaa):ghc11748.hc:
undefined reference to `readline'


Tried linking by hand (not using --make), specifying
-package readline, specifying -lreadline; nothing worked.

/Koen

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Derivable type classes bug?

2004-11-22 Thread Koen Claessen
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 message:


Bug.hs:12:
Could not deduce (Foo a) from the context (Foo [a])
  arising from use of `foo' at Bug.hs:12


Why is the context needed? 'foo' is not a recursive
function?

I guess it is because the default declaration is split up
into several instances:


instance Foo Unit where
  foo _ = 1

instance (Foo a, Foo b) = Foo (a :*: b) where
  foo _ = 2

instance (Foo a, Foo b) = Foo (a :+: b) where
  foo _ = 3


Why not generating:


instance Foo Unit where
  foo _ = 1

instance Foo (a :*: b) where
  foo _ = 2

instance Foo (a :+: b) where
  foo _ = 3


when the context is not needed?

(My motivation is: I have a class like this:

  class Arbitrary a = Shrink a where
shrinkSub :: a - [a]
shrinkSub{| ... |} = ... shrink ...

The definition of shrinkSub is not recursive, it calls a
function 'shrink' from the Arbitrary class instead.)

Regards,
/Koen

PS. Has the implementation of Generics changed from some
earlier compiler version (GHC 5.xx)? I have code lying
around that I am almost certain of used to compile with an
earlier version of GHC (that I do not have access to
anymore).


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Bug in ghc-pkg on SunOS

2002-09-09 Thread Koen Claessen

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
file by using strange flags not recognized by the SunOS
version of ld.

I would be very interested in knowing what these flags
should be. Simply saying '-r' does not work in any case.

/Koen.

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Bug in ghc-pkg on SunOS

2002-09-09 Thread Koen Claessen


 |   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.org/mailman/listinfo/glasgow-haskell-bugs



GHC on Cygwin

2002-06-14 Thread Koen Claessen

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 libraries.

The configure scripts complains about some of these, but not
all. In particular, the following things I had to find out
myself (well, you guys figured it out for me):

  * I was using the wrong version of GHC, (mingw instead of
cygwin),

  * I was using the wrong version of the readline libraries,

  * I was using the wrong version of GHC when I tried to
compile GHCi.

Each of these problems could have easily been flagged by the
configure program, avoiding a lot of problems on my side
(and your side).

However, ghci crashes at start up time! I get the following
behavior:


[lap/bin] -: ./ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.03, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ...
/d/Work/Packages/Ghc/Install/lib/ghc-5.03/HSbase_cbits.o:
unknown symbol `_sigaddset'
ghc-5.03: panic! (the `impossible' happened, GHC version
5.03):
can't load package `base'

Please report it as a compiler bug to
[EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


What to do?
/Koen.

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Bug in GHCi

2002-01-25 Thread Koen Claessen

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 following thing happens in GHCi:

First, I start GHCi (without any arguments). Then I compile
both modules (I am using the command-line here, but that has
nothing to do with the bug.)

  Prelude :!ghc --make B
  ghc-5.02.2: chasing modules from: B
  Compiling A( A.hs, A.o )
  Compiling B( B.hs, ./B.o )

This looks fine. Now, I load B into GHCi:

  Prelude :l B 
  Skipping  A( A.hs, A.o )
  Skipping  B( B.hs, ./B.o )
  Ok, modules loaded: B, A.

Both modules are loaded, and it is the compiled version for 
both.

Now, I am making changes to A:

  B :!touch A.hs

And I recompile the whole thing:

  B :!ghc --make B
  ghc-5.02.2: chasing modules from: B
  Compiling A( A.hs, A.o )
  Compiling B( B.hs, ./B.o )

Still everything is fine. However, when I now reload using
:r, GHCi recognizes that A.hs has changed, but it does *not*
recognize that the new A.o file is already there!

  B :r
  Compiling A( A.hs, interpreted )
  Compiling B( B.hs, interpreted )
  Ok, modules loaded: B, A.

So, I get the interpreted versions of both! (This is wrong.)  
The only way to get the compiled versions, is to load B
freshly:

  B :l B
  Skipping  A( A.hs, A.o )
  Skipping  B( B.hs, ./B.o )
  Ok, modules loaded: B, A.

This leads to the state that I want GHCi to be in.

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Bug in hGetBufBA + hIsEOF

2001-12-10 Thread Koen Claessen

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 ReadMode
 arr - stToIO (newCharArray (0,2048))
 n1  - hGetBufBA han arr 2048
 --eof - hIsEOF han
 n2  - hGetBufBA han arr 2048
 print (n1,n2)

I am using solaris and GHC 5.02.1.

Thanks,
/Koen.


module DataStream where

import IO
import IOExts
import MutableArray
import ST
import GlaExts

main =
  do dat - readFileData DataStream.hs
 writeFileData copy.hs dat


-- Data

newtype Data = MkData [(Int,MutableByteArray RealWorld Int)]


-- reading, writing

hGetData :: Handle - IO Data
hGetData han =
  do xs - get
 return (MkData xs)
 where
  get =
unsafeInterleaveIO (
  do arr - stToIO (newCharArray (0,blockSize))
 putStrLn Reading ...
 n   - hGetBufBA han arr blockSize
 putStrLn ((read  ++ show n ++  bytes))
 --eof - hIsEOF han
 let eof = n /= blockSize
 xs  - if eof then return [] else do hIsEOF han; get
 return ((n,arr):xs)
)

hPutData :: Handle - Data - IO ()
hPutData han (MkData xs) =
  sequence_ [ do hPutBufBA han arr n
 putStrLn ((written  ++ show n ++  bytes))
| (n,arr) - xs ]

blockSize :: Int
blockSize = 2048


-- files

readFileData :: FilePath - IO Data
readFileData file =
  do han - openFile file ReadMode
 hGetData han

writeFileData :: FilePath - Data - IO ()
writeFileData file dat =
  do han - openFile file WriteMode
 hPutData han dat
 hClose han

appendFileData :: FilePath - Data - IO ()
appendFileData file dat =
  do han - openFile file AppendMode
 hPutData han dat
 hClose han

{-

-- operations

toData :: String - Data
toData s =
  unsafePerformST (
do arr - newCharArray (0,n)
   sequence_ [ writeCharArray arr i c | (i,c) - [0..] `zip` s ]
   return (MkData [(n,arr)])
  )
 where
  n = length s - 1

fromData :: Data - String
fromData (MkData xs) =
  concat (unsafePerformST (sequence [ read n arr | (n,arr) - xs ]))
 where
  read n arr =
sequence [ readCharArray arr i | i - [0..n] ]

(+++) :: Data - Data - Data
MkData xs +++ MkData ys = MkData (xs ++ ys)


-- helpers

unsafePerformST :: ST RealWorld a - a
unsafePerformST m = unsafePerformIO (stToIO m)
-}

-- the end.



module Main where

import IO
import IOExts
import MutableArray
import ST
import GlaExts

main =
  do han - openFile test ReadMode
 arr - stToIO (newCharArray (0,2048))
 n1  - hGetBufBA han arr 2048
 --eof - hIsEOF han
 n2  - hGetBufBA han arr 2048
 print (n1,n2)


 
 





Bug in GHCi

2001-10-31 Thread Koen Claessen

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 
behavior, since if I load the module in GHCi, it just 
complains, but allows me to continue. (It is rather 
cumbersome to have to reload all packages just because one 
made a spelling mistake in the import declaration).

The second bug is when one loads an empty module (empty 
file) into GHCi, it complains with *** Exception: 
reAllocMem.

/Koen



___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



ghc -O

2001-10-31 Thread Koen Claessen

Simon Marlow wrote:

 | Thanks, I've fixed both of these.

Great!

Now I have discovered another bug in GHC. It happens very
often that I get a the impossible happened when I run GHC
with the -O flag.

Here is an example. I attached two files. When running ghc
-o --make 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:GPL

Comments:

This module implements fast and space-efficient monadic parser
combinators. It is inspired by Daan Leijen's Parsec library.
The aim was to get a library that was equally fast, without
having to use the cumbersome try combinator. (That combinator
is still supported, but is defined to be the identity function.)
This aim is achieved by using a paralell choice combinator,
instead of using backtracking.

The result is a library that is nearly as fast as Daan's, and
is (almost) compatible with it. (The types in this module are
a bit more general than Daan's.)

A part of the code (the parser combinators like many) is simply
taken from Daan's original code. I hope he doesn't mind :-)

-}

module Parsek
  -- basic parser type
  ( Parser-- :: * - * - *; Functor, Monad, MonadPlus
  , Expect-- :: *; = [String]
  , Unexpect  -- :: *; = [String]
  
  -- parsers
  , satisfy   -- :: Show s = (s - Bool) - Parser s s
  , lookAhead -- :: Show s = (s - Bool) - Parser s s
  , string-- :: (Eq s, Show s) = [s] - Parser s [s]
  
  , char  -- :: Eq s = s - Parser s s
  , noneOf-- :: Eq s = [s] - Parser s s
  , oneOf -- :: Eq s = [s] - Parser s s
  
  , spaces-- :: Parser Char ()
  , space -- :: Parser Char Char
  , newline   -- :: Parser Char Char
  , tab   -- :: Parser Char Char
  , upper -- :: Parser Char Char
  , lower -- :: Parser Char Char
  , alphaNum  -- :: Parser Char Char
  , letter-- :: Parser Char Char
  , digit -- :: Parser Char Char
  , hexDigit  -- :: Parser Char Char
  , octDigit  -- :: Parser Char Char
  , anyChar   -- :: Parser s s
  , anySymbol -- :: Parser s s

  -- parser combinators
  , label -- :: String - Parser s a - Parser s a
  , (?) -- :: String - Parser s a - Parser s a
  , pzero -- :: Parser s a
  , (|) -- :: Parser s a - Parser s a - Parser s a
  , try   -- :: Parser s a - Parser s a; = id
  , choice-- :: [Parser s a] - Parser s a
  , option-- :: a - Parser s a - Parser s a
  , optional  -- :: Parser s a - Parser s ()
  , between   -- :: Parser s open - Parser s close - Parser s a - Parser s a
  , count -- :: Int - Parser s a - Parser s [a]

  , chainl1   -- :: Parser s a - Parser s (a - a - a) - Parser s a
  , chainl-- :: Parser s a - Parser s (a - a - a) - a - Parser s a
  , chainr1   -- :: Parser s a - Parser s (a - a - a) - Parser s a
  , chainr-- :: Parser s a - Parser s (a - a - a) - a - Parser s a

  , skipMany1 -- :: Parser s a - Parser s ()
  , skipMany  -- :: Parser s a - Parser s ()
  , many1 -- :: Parser s a - Parser s [a]
  , many  -- :: Parser s a - Parser s [a]
  , sepBy1-- :: Parser s a - Parser s sep - Parser s [a]
  , sepBy -- :: Parser s a - Parser s sep - Parser s [a]
  
  -- parsing  parse methods
  , ParseMethod   -- :: * - * - * - * - *
  , ParseResult   -- :: * - * - *; = Either (e, Expect, Unexpect) r
  , parseFromFile -- :: Parser Char a - ParseMethod Char a e r - FilePath - IO 
(ParseResult e r)
  , parse -- :: Parser s a - ParseMethod s a e r - [s] - ParseResult e r

  , shortestResult -- :: ParseMethod s a (Maybe s) a
  , longestResult  -- :: ParseMethod s a (Maybe s) a
  , longestResults -- :: ParseMethod s a (Maybe s) [a]
  , allResults -- :: ParseMethod s a (Maybe s) [a]
  , completeResults-- :: ParseMethod s a (Maybe s) [a]
  
  , shortestResultWithLeftover -- :: ParseMethod s a (Maybe s) (a,[s])
  , longestResultWithLeftover  -- :: ParseMethod s a (Maybe s) (a,[s])
  , longestResultsWithLeftover -- :: ParseMethod s a (Maybe s) ([a],[s])
  , allResultsWithLeftover -- :: ParseMethod s a (Maybe s) [(a,[s])]
  
  , completeResultsWithLine-- :: ParseMethod Char a Int [a]
  )
 where
  
import Monad
  ( MonadPlus(..)
  )

import List
  ( union
  , intersperse
  )

import Char

infix  0 ?
infixr 1 |

-
-- type Parser

newtype Parser s a
  = Parser (forall res . (a - Expect - P s res) - Expect - P s res)

-- type P; parsing processes

data P s res

Flags in GHCi

2001-10-03 Thread Koen Claessen

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 dynamic libraries).

This is strange behavior, not to call it a bug.

It might be because the first case looks for files called
*.so.1, the second case for files called *.so, but I am
not sure. (Moreover, I do not understand the difference
between these files anyway.)

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Socket documentation

2001-10-02 Thread Koen Claessen

Hi,

The function mkPortNumber is gone from the Socket library:

  Prelude :t Socket.mkPortNumber

  interactive:1: Variable not in scope: `Socket.mkPortNumber'

Though it is still mentioned in the documentation for
GHC-5.02.

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: FFI in GHCi 5.02

2001-09-28 Thread Koen Claessen

Manuel M. T. Chakravarty wrote:

 |  ghc-5.02: panic! (the `impossible' happened, GHC version
 |  5.02):
 |  ByteCodeFFI.mkMarshalCode_wrk(sparc) C_
 | 
 |  Please report it as a compiler bug to
 |  [EMAIL PROTECTED],
 |  or http://sourceforge.net/projects/ghc/.
 :
 | I vaguely remember that Julian wrote that the
 | interpreter support for the FFI is limited to x86 for
 | the moment.  You still should be fine if you compile
 | all modules including a foreign import declaration.

I know I should be fine compiling my modules.

I am just reporting 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 5424  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



FFI in GHCi 5.02

2001-09-27 Thread Koen Claessen

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.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package std ... linking ... done.
Loading package lang ... linking ... done.
Loading object (dynamic) yahu ... done
final link ... done.
Compiling YahuHeap (
/users/mdstud/afp01/Resources/YahuNew/YahuHeap.hs,
interpreted )
Compiling YahuTk   (
/users/mdstud/afp01/Resources/YahuNew/YahuTk.hs, interpreted
)
ghc-5.02: panic! (the `impossible' happened, GHC version
5.02):
ByteCodeFFI.mkMarshalCode_wrk(sparc) C_

Please report it as a compiler bug to
[EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


It seems something is wrong with the FFI!

/Koen.

[1] Yahu, downloadable from:
http://www.cs.chalmers.se/Cs/Grundutb/Kurser/afp/tools.html


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Bug in Time module

2001-09-26 Thread Koen Claessen

Hi,

I discovered a bug in the Time module.  If I run the
following code snippet:

  main :: IO ()
  main =
do t0 - getClockTime
   system sleep 120
   t1 - getClockTime
   print (t1 `diffClockTimes` t0)

The TimeDiff value has a tdSec field greater than 59, and 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, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Bug in Time module

2001-09-26 Thread Koen Claessen


 | 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 if leap seconds are taken into
 | account.

You are absolutely right of course. Shouldn't this be
regarded as a bug in the Haskell'98 spec then? It is not
sure to me at all what a value of TimeDiff really means.

Maybe TimeDiff should only contain the fields: tdDay,
tdHour, tdMin, tdSec, and tdPicosec?

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Eq Socket

2001-08-09 Thread Koen Claessen

Hi,

In the GHC manual for the Socket library it says:

  data Socket -- instance of: Eq, Show

But Socket does not seem to be an instance of Eq, as the
following program shows:

  module Apa where

  import Socket

  foo :: Socket - Bool
  foo x = x == x

When executing ghc -package 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  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Generics

2001-08-01 Thread Koen Claessen

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
 op {| a :*: b |} (Inl x) = True

 op2 :: a - Bool
 op {| p :*: q |} (Inr y) = False

This does not make any sense to me! (op is defined, but
not declared; in both cases the type is :*:, but the
argument is Inl and Inr).

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Package

2001-07-31 Thread Koen Claessen

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-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Package

2001-07-31 Thread Koen Claessen

Simon Marlow wrote:

 |  It would be nice if there were a flag to ghc and to
 |  ghc-pkg that also allowes using a local package
 |  file.
 |
 | Yup, that would be a nice feature. There's some
 | complication in that GHC currently uses the location
 | of the package.conf file 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  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



GHCi and .o files

2001-07-31 Thread Koen Claessen

Hi,

I have the following strange situation. I am running GHC(i)
5 on Solaris.

I have the following files:

  primtk.c
  PrimTk.hs
  Yahu.hs

Where

  * primtk.c defines some C functions,

  * PrimTk.hs contains the foreign import declarations
of these functions, and

  * Yahu.hs is a Main module that uses PrimTk.hs.

When I compile everything in the following way:

   gcc -c primtk.c -o primtk.o
   ghc primtk.o --make Yahu.hs

The resulting executable works fine!

However, when I try to do the same thing in GHCi:

   gcc -c primtk.c -o primtk.o
   ghci primtk.o Yahu.hs
  ...

Everything loads as expected (!), I can even run the
program, but unfortunately, while running my program, the
string constants (data part) in primtk.c/primtk.o get
overwritten by other functions.

My question is: is this a bug in the dynamic linking of
static object files in GHCi?

If so, I'd be happy to send the source files, (though there
are rather many of them.)

If I am not supposed to do it in this way, please tell me
how I am supposed to do it. I tried the following:

   gcc -c primtk.c -fPIC -shared -o primtk.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 Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Bug in type inference

2001-07-25 Thread Koen Claessen

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 :: ST a ()

The behaviour is present in GHC 5.00.2, but has been
detected in earlier versions as well.

It does not have anything to do with GHCi, because regular
ghc makes the same mistake.

/Koen.


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Bug in GHCi

2001-07-09 Thread Koen Claessen

Hello all,

I have been using GHCi now for some time. There is one bug
that keeps coming back.

When I press control-C during the evaluation of an
expression, I get back to the prompt, and GHCi says:

  Interrupted.

I make some changes to my files, and type :r, then GHCi
says:

  Interrupted.

(It does not load anything!) I press :r again, and then
one of the following three things happens:

  1. GHCi says Interrupted. again.

  2. It reloads, and everything is fine.

  3. It crashes.

When it crashes, it sometimes says:

  unloadObj: can't find `Machine.o' to unload
  ghc-5.00.2: panic! (the `impossible' happened, GHC version
  5.00.2):
unloadObj: failed

  Please report it as a compiler bug to
  [EMAIL PROTECTED],
  or http://sourceforge.net/projects/ghc/.

Now, it might have to do with the fact that I have a lot of
calls to 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.

--
Koen Claessen http://www.cs.chalmers.se/~koen
phone:+46-31-772 5424  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: Problem with the GHC RNG.

2000-01-24 Thread Koen Claessen

Andy Gill wrote:

 | I'm trying to use QuickCheck inside GHC (has this been
 | tried before?)

I think Chris Okasaki tried that. Certainly not me, and I
don't think John either.

 | The final example is great; lots of good test data.
 | However the tests before point to some serious
 | shortcoming of the GHC RNG.

Hmm... The Hugs RNG had some problems a while ago too, but
this was fixed in a newer version. The problem was that
the function "split" should return two new, independent
generators. The Hugs definition looked something like:

  split gen = (gen, new gen)

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]
-
Chalmers University of Technology, Gothenburg, Sweden




Bug?

1999-05-13 Thread Koen Claessen

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.chalmers.se/~koen,
Chalmers University of Technology.



Possible bug

1999-01-27 Thread Koen Claessen

Hi,

I have been doing probability theory tests. One of them involved the so
called "secretary problem". Here is my code:


module Main where

import Random
import List
import IO

type Process = [Integer] - Bool

simulate :: Int - Integer - Process - IO Double
simulate n m proc =
  do tries - accumulate [ map proc (randomIO (1,m)) | _ - [1..n] ]
 return (length (filter id tries) // n)
 where
  n // m = fromInt n / fromInt m

sim :: Int - IO Double
sim k = simulate 1000 100 proc
 where
  proc rs = [best] == take 1 afterk
   where
xs = take 100 (nub rs)
best   = 100
bestk  = maximum (take k xs)
afterk = dropWhile ( bestk) (drop k xs)

main :: IO ()
main =
  do ps - accumulate [ sim k | k - [35..39] ]
 print ps


When I run this module with ghc-4.01, I get _wrong_ results, and a bus
error:


[koen] -: ghc-4.01 -O secretary.hs -o secretary
ghc-4.01: module version changed to 2; reason: usages changed
[koen] -: secretary
[3.3e-2,0.0,0.0,0.354,0.174]
Bus error


The right behavior should be like:


[koen] -: hbc secretary.hs -o secretary
[koen] -: 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.




RE: H/Direct 0.16

1999-01-03 Thread Koen Claessen

Hi,

(I was trying to make H/Direct work with Hugs).

It was a lot of work to find it, but now I have removed the recursive
dependency between AddrBits and HDirect. AddrBits only needed
HDirect.Octet, which was the same as AddrBits.Octet, and HDirect.Ptr,
which was the same as Pointer.Ptr.

Now, I get another problem:

ERROR "../../lib/HDirect.lhs" (line 201): Type error in application
*** Expression : writeI64 ptr (toInt lo) (toInt hi)
*** Term   : toInt hi
*** Type   : Int
*** Does not match : Int32

I am sorry, but I have to give up at this point.

Regards,
Koen.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden




GreenCard 2.0 bug

1999-01-03 Thread Koen Claessen

Hi,

I have (maybe temporarily) given up on H/Direct. The system
just seems way too heavyweight to use for the simple
application I had in mind (let alone to install everything).

Therefore, I tried GreenCard. The compiler works fine, but
when I compile the c-code, it complains about "GreenCard.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 Technology, Gothenburg, Sweden




H/Direct

1999-01-02 Thread Koen Claessen

Hi,

Okay, after some compilation time I hit a new problem.
This time I get the following error:

  Utils.lhs:345: parse error on input `.'

The problem seems to be the following piece of code in Utils.lhs:

  data FieldInfo a
   = forall i .  -- not really needed, but convenient.
  FieldInfo
String -- field label
Bool   -- True = optional
(String - Maybe (i,String))
 (i - a - a)

In my case, it is not "convenient" :-).

It seems that the compiler does not automatically get
the options that allow for forall quantification. I am
using ghc-4.04 on Solaris, and not the recommended
ghc-4.03, but that should not be a problem?

I tried adding the flag -fglasgow-exts, but that generates
another (very strange) error:

  Utils.lhs:22: parse error on input `(#'

On the following 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.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden