Read file fails on Windows

2001-02-22 Thread Meurig Sage

Hi 
I just installed ghc-4.08.2 on Windows NT. I tried the following program 

module Main where
import System

main = do
 argv <- getArgs
 case argv of
 (inp:out:[]) -> do
 contents <- readFile inp  
 writeFile out contents

 _ -> putStr "usage_msg "

I compiled with ghc -O -o test test.hs

I ran it with 

test re_tests re_testsout

When running the program it failed with 

Fail: failed
Action: openFile
Reason: (error code: 0) re_tests

The same program worked fine when compiled with ghc-4.08.1.

Meurig


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



bug in dupChan

2001-01-24 Thread Meurig Sage



Hi 
I think that there's a bug in dupChan in 
Chan.lhs
 
I tried the following program. 
 main = do chan <- 
newChan ch <- dupChan chan writeChan chan "done" x 
<- readChan chan y <- readChan ch prnt ("Got "++x ++" 
"++y)
 
Now if I remember correctly this should print "Got 
done done".
 
Instead it exits with 
C:\Test\test.exe: no threads to run:  infinite 
loop or deadlock?
 
I looked for the code for dupChan in hslibs and it 
says
dupChan :: Chan a -> IO (Chan a)dupChan (Chan _read write) = 
do   new_read <- newEmptyMVar   
hole <- readMVar write   putMVar 
new_read hole   return (Chan new_read write)
 
Shouldn't this instead be 
 
dupChan :: Chan a -> IO (Chan a)dupChan 
(Chan _read write) = do   new_read <- 
newEmptyMVar   hole <- readMVar 
write   putMVar new_read hole
** putMVar write hole **   
return (Chan new_read write)
 
That's at least what the Concurrent haskell paper 
says.
 
Hugs 98 seems to have the same bug with its 
library.
 
Meurig


hello world fails to run on windows

2001-01-22 Thread Meurig Sage



Hi
I installed ghc-4.08.1 earlier today on a Windows 
NT box. I tried out hello world. I compiled with:
 
ghc -O -static -o main Main.hs
 
Compilation went fine. But when I tried to run the 
program it produced no output. I then experimented further. I got TclHaskell 
up & running and successfully got it to produce a simple user 
interface. However, if I put in a call to putStr into the code the program exits 
prematurely. 
 
I'm running Windows NT, with cygwin v1.1 installed 
today. 
 
Meurig


finalisers not being run

1999-12-10 Thread Meurig Sage

Hi,
I've got the following program. It depends heavily on finalisers being run
regularly as it goes along. I therefore call yield regularly to try to
ensure this.
This works perfectly under the original ghc-4.04 release, weak pointers are
garbage collected and finalisers run regularly.

However, with the cvs release of ghc this does not happen. When I run the
program normally finalisers are only run at the end of the program. This is
despite the fact that their associated weak pointers have been garbage
collected much earlier, and yield is being called regularly. If I run with
+RTS -G1, which makes life even better in 4.04 (as weak pointers are garbage
collected more regularly), with 4.05 life gets even worse. The finalisers
are NEVER run. This happens whether I compile with or without -O.

Perplexed,
 Meurig

PS I enclose the program.
I run it with
main 1000 10

The first argument says how many times to loop round.
The second says how regularly to call yield.

The program prints killed when a weak pointer dies, and finalised when a
weak pointer is finalised.



 sendsimon.tar.gz


cvs ghc problems

1999-12-09 Thread Meurig Sage

Hi I compiled up the cvs ghc from yesterday (7 Dec 1999). This was on NT.
I had one problem when actually compiling.
In config.mk.in line 150 has been changed to:

WithGhcHc = $(HC)

from

WithGhcHc = @WithHc@

This caused circular dependencies when compiling up ghc/compiler.


==fptools== make all --unix --no-print-directory -r;
 in /meurig/cvs/fptools/ghc/compiler

../../mk/suffix.mk:50: *** Recursive variable `HC' references itself
(eventually).  Stop.

This was fixed by changing WithGhcHc back to its original value.

After that ghc compiled up fine.
However, the heap profiling bug I mailed, last Friday, is still there. The
code I sent still causes the ghc compiled binary to core dump when run with
+RTS -h.

Meurig




ghc coredumps with profiling

1999-12-03 Thread Meurig Sage

Hi
I compiled up the attached set of files using Tuesday's cvs ghc. It's
compiled with -prof -auto-all -caf-all. It runs fine without heap profiling,
but core dumps with it. This was running on windows NT.

I ran it with the following arguments:

main 1000 +RTS -h

Meurig

 crash.tar.gz


compiling cvs from Nov 30

1999-12-01 Thread Meurig Sage

Hi
When compiling the cvs ghc and hslibs from Nov 30 I found the following
problem.

Compiling hslibs/util/Select.lhs failed because it imported posix interface
files.
../../ghc/driver/ghc-inplace -syslib concurrent -syslib
posix -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing -O -split-objs -odir
Select -static-static -c Select.lhs -o Select.o -osuf o

Select.lhs:22: Could not find valid interface file `Posix'

Select.lhs:28: Could not find valid interface file `PosixUtil'

Compilation had errors

The Makefile in hslibs compiles util before posix. Shouldn't this be done
the other way round? When I compiled posix, then Select.lhs it worked fine.

Meurig




heap profiling with ghc

1999-11-25 Thread Meurig Sage

Hi,
I got round yesterday's compilation problem (panic on interface file), by
compiling the module Widgets.lhs without -O.
The demo program now compiles.
It runs normally and will happily give a time profile.
./demos +RTS -pT

However, when run with heap profiling

./demos +RTS -hC

it crashes with

demos: fatal error: heapCensus

Any thoughts?

Meurig





cvs ghc crashes when compiling

1999-11-23 Thread Meurig Sage

Hi,
I tried compiling a cvs copy of ghc from Monday 22 November.
This was on Windows NT. The compiler was compiled using the binary
ghc-4.045 binary release. It crashed when compiling PrelBase.


==fptools== make all --unix --no-print-directory -r;
 in /meurig/cvs/fptools/ghc/lib


===fptools== Recursively making `all' in std exts concurrent posix misc ...
PWD = /meurig/cvs/fptools/ghc/lib


==fptools== make all --unix --no-print-directory -r;
 in /meurig/cvs/fptools/ghc/lib/std

rm -f PrelBase.o ; if [ ! -d PrelBase ]; then mkdir PrelBase; else find
PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi ;
../../driver/ghc-inplace -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing -O
 -split-objs -odir PrelBase -fcompiling-prelude -static  -H12m  -v -c
PrelBase.lhs -o PrelBase.o -osuf o
The Glorious Glasgow Haskell Compilation System, version 4.05

literate pre-processor:
 echo '#line 1 "PrelBase.lhs"' > /tmp/ghc17024.lpp &&
/meurig/cvs/fptools/ghc/driver/../utils/unlit/unlit  PrelBase.lhs -  >>
/tmp/ghc17024.lpp

real 0m0.010s
user 0m0.010s
sys 0m0.000s
Found OPTIONS -fno-implicit-prelude in /tmp/ghc17024.lpp

Effective command
line: -fno-implicit-prelude -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
 -O -split-objs -odir PrelBase -fcompiling-prelude -static -H12m -v -c -o
PrelBase.o -osuf o

Haskellised C pre-processor:
 echo '{-# LINE 1 "PrelBase.lhs" -}' > /tmp/ghc17024.cpp &&
/meurig/cvs/fptools/ghc/driver/../utils/hscpp/hscpp -v  -D__HASKELL__=98 -D_
_HASKELL1__=5 -D__GLASGOW_HASKELL__=405 -D__HASKELL98__ -D__CONCURRENT_HASKE
LL__ -I. -I/meurig/cvs/fptools/ghc/driver/../includes /tmp/ghc17024.lpp >>
/tmp/ghc17024.cpp

real 0m0.000s
user 0m0.000s
sys 0m0.000s
hscpp:CPP invoked:
gcc -E -undef -traditional -D__HASKELL__=98 -D__HASKELL1__=5 -D__GLASGOW_HAS
KELL__=405 -D__HASKELL98__ -D__CONCURRENT_HASKELL__ -I. -I/meurig/cvs/fptool
s/ghc/driver/../includes - 


confusing error message

1999-09-10 Thread Meurig Sage

ghc-4.04 gives the following confusing error message:

compiling with ghc-4.04 -fglasgow-exts -c Test.hs

Test.hs:8:
None of the type variable(s) in the constraint `Eq a'
appears in the type `Set a -> Set a -> Set a'
In the type signature for `unionSets'

Compilation had errors

module Test where

unionSetB :: Eq a => Set a -> Set a -> Set a
unionSetB (s1 :: Set a) s2 = unionSets s1 s2
 where
   unionSets :: Eq a => Set a -> Set a -> Set a
   unionSets a b = a

Ok, I know why this happens, because a is no longer free in unionSets
because of the pattern signature, but initially it confused me looking at it
trying to work out why a /= a.

(Incidently hugs accepts this code without any complaints)

Meurig



Re: getArgs delivers only emty Lists

1999-06-16 Thread Meurig Sage

>Hi,
>
>fix is available from
>
>  http://www.dcs.gla.ac.uk/~sof/ghc-win32.html
>
>--sigbjorn
>

The fix doesn't quite work.
Eg

running
$ghc-4.03 -o main main.hs
$./main a b +RTS -H20M
["a","b","+RTS","-H20M"]

where main.hs is

module Main where
import System
main = do
 as <- getArgs
 print as




Re: Compilation problem with ghc-4.03 win32

1999-06-10 Thread Meurig Sage

>
>Add -mno-cygwin to the gcc command line when compiling any .c's.
>
>--sigbjorn


Thanks, that fixed the initial problem but now I've got another one.
Running the program causes it to crash with the application error:
The instruction at "0x77f6ce0c" referenced memory at "0x0010". The
memory could not be "written".

This happens whether I compile with -static or without.

To run it I use
./tclexe ./main

Where tclexe is the following

-
#!/bin/sh

# The root of the cygwin shared libraries. Allowing access to Tk and Tcl.

root=/ExtraUtils/cygnus/cygwin-b20/share

export TK_LIBRARY TCL_LIBRARY
TK_LIBRARY=$root/tk8.0/
TCL_LIBRARY=$root/tcl8.0/

exec "$@"

---
Thanks
  Meurig




Compilation problem with ghc-4.03 win32

1999-06-10 Thread Meurig Sage

Using the new ghc-4.03 binary snapshot on Windows NT I get the following
problem compiling a file.

gcc -c tclhaskell.c
ghc-4.03 -fglasgow-exts '-#include "tclhaskell.h"' -o main.exe Main.hs
tclhaskell.o -ltcl80 -ltk80

tclhaskell.o(.text+0x69):tclhaskell.c: undefined reference to `_impure_ptr'
tclhaskell.o(.text+0x34b):tclhaskell.c: undefined reference to `_impure_ptr'
tclhaskell.o(.text+0x3f2):tclhaskell.c: undefined reference to `_impure_ptr'
tclhaskell.o(.text+0x450):tclhaskell.c: undefined reference to `_impure_ptr'
tclhaskell.o(.text+0x487):tclhaskell.c: undefined reference to `_impure_ptr'
tclhaskell.o(.text+0x51e):tclhaskell.c: more undefined references to
`_impure_ptr' follow
collect2: ld returned 1 exit status

I also tried compiling with -static to see if it made any difference but no
change.

Compiling with ghc-4.02 works without problem.

I've enclosed the necessary files.

Thanks
  Meurig



 Main.hs
 tclhaskell.c
 tclhaskell.h


Re: ghc-4.02 crashes with Windows NT - followup

1999-02-26 Thread Meurig Sage

Meurig Sage wrote:

> Hi,
> I'm using ghc-4.02 on Windows NT. I downloaded the binary installshield
> and the cygwin B20.1. I then compiled up a large program.
>
> The compiled program crashes some of the time with the following error:
> ...
> This problem goes away if I increase the heap size sufficiently with -H.
> So it looks like its another garbage collector bug.
>

As a quick follow up, I should have said. The same program runs fine with
ghc-4.02 under linux.
Meurig

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]





Re: Segmentation faults with ghc-4.02 code

1999-02-22 Thread Meurig Sage

Simon Marlow wrote:

> > I tried to compile the following program with both ghc-3.02
> > and ghc-4.02  (pathlevel 1), using the linux glibc binary releases. The
> > 3.02 one works fine but the code produced by 4.02 segmentation faults
> > when I try to run
>
> I can't repeat this one - the program compiles fine and pops up a button
> when I run it.  This is with stock 4.02 on Linux.
> ...
> Perhaps it's picking up the wrong versions of libraries or something?

Yep, thanks it does seem to have been a weird library thing.  Changing to your
compilation commands seems to have worked.

Sorry for the hassle,
Meurig

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]





Segmentation faults with ghc-4.02 code

1999-02-19 Thread Meurig Sage
if (strlen(str)+1>slot_size()) {
tkh_error("event string too large");
return;
  }
  if (queue_full) {
tkh_error("event buffer overrun");
return;
  }
  strcpy(event_buffer+slot_base(queue_tail), str);
  inc_index(&queue_tail);
  if (queue_head==queue_tail)
queue_full= 1;
}

static char *dequeue(void)
{
  char *item = event_buffer+slot_base(queue_head);

  if (queue_empty())
tkh_abort("empty queue");

  inc_index(&queue_head);
  queue_full= 0;
  return item;
}


/* 
 *  haskellEventCmd:
 *(Registered as a new Tcl command: see initTcl, below.)
 *
 *This is used as part of the callback mechanism: it inserts
 *argument string into the TclHaskell event queue, triggering
 *primRunTcl to break its loop so that TclHaskell can retrieve
 *the event descriptor woth primGetEvent.
 */

static int haskellEventCmd(dummy, interp, argc, argv)
ClientData dummy;   /* Not used. */
Tcl_Interp *interp; /* Current interpreter. */
int argc;   /* Number of arguments. */
char **argv;/* Argument strings. */
{

if (tcl_debug) {
fprintf(stderr, "[Queueing Event: %s]\n", argv[1]);
}

/* ignore surplus arguments as passed to scale commands, for example
*/

if (argc<2){
Tcl_AppendResult(interp,
"haskellEvent: should have at least 1 argument",
(char *) NULL);
return TCL_ERROR;
}
enqueue(argv[1]);

return TCL_OK;
}


/* 
 *  Implementation of Haskell Primitives
 */



/* 
 *  primTclDebug:
 *sets the debug flag
 */

void primTclDebug (int flg)
{
  tcl_debug = flg;
}


/* 
 *  primInitTcl:
 *initializes Tcl/Tk,
 *and the new new command `haskellEvent',
 *return 1 if successful, 0 otherwise.
 */

int primInitTcl (void) {


if (tcl_debug) {
fprintf(stderr, "[Initialize Tcl]\n");
}

init_queue();  /* Reset commuication buffers */

interp = Tcl_CreateInterp();

Tcl_SetVar(interp, "tcl_interactive", "0", TCL_GLOBAL_ONLY);

if (Tcl_Init(interp) == TCL_ERROR) {
 fprintf(stderr, "%s\n", interp->result);
 return(0);
}

if (Tk_Init(interp) == TCL_ERROR) {
 fprintf(stderr, "%s\n", interp->result);
 return(0);
}


/* Extensions for tcl: */

Tcl_CreateCommand(interp, "haskellEvent", haskellEventCmd,
(ClientData) NULL, (void (*)()) NULL);

return(1);
}



/* 
 *  primRunTcl:
 *runs Tcl's event loop until one or more events
 *are queued for Haskell processing, returning 1
 *if `.' has been destroyed, 0 otherwise.
 */

int primRunTcl (void) {

if (tcl_debug) {
fprintf(stderr, "[TclHaskell is waiting for an event...]\n");
}

while ((Tk_GetNumMainWindows() > 0) && (queue_empty())) {
  Tk_DoOneEvent(0);
}
return (Tk_GetNumMainWindows() > 0);
}



/* 
 *  primExecuteTcl:
 *perform Tcl command and return result to TclHaskell
 */

static char *executeTcl (char *cmd);

char *primExecuteTcl (char *cmd)
{
  char *result;

  result= executeTcl(cmd);
  if (tcl_debug) fprintf(stderr, "  %s <- %s\n", result, cmd);
  return result;
}

void primExecuteTcl_ (char *cmd)
{
  (void) executeTcl(cmd);
  if (tcl_debug) fprintf(stderr, "  %s\n", cmd);
}

static char *executeTcl (char *cmd)
{
   if (Tcl_Eval(interp,cmd) != TCL_OK) {
   fprintf(stderr, "Tk/Tcl: %s\n", interp->result);
   return ("");
   }
   return (interp -> result);
}



/* 
 *  primGetEvent:
 *return the event buffer to gofer
 */

char *primGetEvent(void) {

  if (queue_empty())
return ("");
  else {
char *item = dequeue();

if (tcl_debug) {
  fprintf (stderr, "[Processing event %s]\n", item);
}
return(item);
  }
}



/* 
 *  primSetVar:
 *    write user output in tcl variable
 *in this way, special tcl characters
 *like [, $, } etc

Problem with ghc-4.02

1999-02-11 Thread Meurig Sage

Hi
I'm trying out ghc-4.02 using the linux binary release.
GHC dies with the following error message when trying to compile one of
my files:
ghc-4.02 -fvia-C -fglasgow-exts -O -c TclWidgets.hs
hsc: fatal error: evacuate: strange closure type

I've tried compiling it without the -O and with -Onot but don't get
anywhere.
With an earlier module I get the following warning:

/tmp/ghc12270.hc:994: warning: `c9h2_closure' was declared `extern' and
later `static'
/tmp/ghc12270.hc:1063: warning: `c9h5_closure' was declared `extern' and
later `static'

Any ideas?
The source files are all bundled up at
http://www.dcs.gla.ac.uk/~meurig/TclHaskell.tar.gz
Meurig

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]





Re: -monly-N-regs ?

1997-08-06 Thread Meurig Sage

Ian Collier wrote:
> 
> While I was trying to compiling ArrBase.o on i386-unknown-solaris2 this
> message appeared:
> 
> >/tmp/ghc18527.hc:6388: fixed or forbidden register was spilled.
> >This may be due to a compiler bug or to impossible asm
> >statements or clauses.
> 
This happened with me, with ghc-2.04 aswell. Sigbjorn said
"the backend is trying to steal more x86 registers than gcc can handle".
The solution is to do the following, compile ArrBase separately using:

make EXTRA_HC_OPTS=-monly-2-regs ghc/ArrBase.o

Then go on with the make.
--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



labelled fields in ghc-2.04

1997-06-12 Thread Meurig Sage

This bug was mentioned during ghc-2.03's time. I thought it had been
fixed since. But the following code still does not compile in ghc-2.04:

--
data X = A {a :: Int} | B {a :: Int} 
--
test2.lhs:2:
Conflicting definitions for: `a'
Defined at test2.lhs:3
Defined at test2.lhs:3


Compilation had errors 
--
--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



Universally-quantified data type fields

1997-06-12 Thread Meurig Sage

Hi
 I've managed to get a basic version of ghc-2.04 to build but when
trying to play with the new features I came across a problem.

I wanted to try out the new Universally-quantified data type fields. So
I took an example from Simon's web page.

---
\begin{code}
module Test where
data T a = T1 (All b => b -> b -> b) a
\end{code} 
---

I tried compiling it, but it failed:

---
ascension{meurig}227: ghc-2.04 -fglasgow-exts -c test.lhs

test.lhs:5:
Type constructor or class not in scope: `All'


Compilation had errors  
---
What compiler flags am I missing, that I need, to get this to work?
Sorry if I'm missing something obvious.

Cheers
 Meurig
--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



Another ghc-2.04 compiling problem

1997-06-12 Thread Meurig Sage

Sigbjorn Finne wrote:
> 
> Einar Wolfgang Karlsen writes:
> >
> >
> > I am using the MatchPS module for loads of tool integration tasks (peeking
> > into the output from those tools looking for important signs and relevant
> > messages).
> >
> > Unfortunately, MatchPS.matchPS seems to be quite restrictive wrt. the
> > size of the string that can be matched against a pattern: it fails if the
> > length of the (matched?) string is greater than 2560 (Hm).
> >
>you'll need to compile ArrBase with -monly-3-regs, the backend is
>trying to steal more x86 registers than gcc can handle. If you're still
>getting the same error, try -monly-2-regs

The earlier problem I had with ArrBase disappeared when I used
-monly-2-regs. Thanks. But I've got another problem now...

When trying to compile a concurrent profiled version of ghc-2.04 on
i386-unknown-solaris2, I came across the problem below.

Cheers
  Meurig

../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
-split-objs -odir required/System -hisuf mr_hi -prof -concurrent -prof
-GPrelude   -c required/System.lhs -o required/System.mr_o -osuf mr_o
ghc: WARNING: splitting objects when profiling will *BREAK* if any
_scc_s are present!
<>
Module version unchanged at 1
/tmp/ghc27506.hc:2682: parse error before `case'
/tmp/ghc27506.hc:2687: parse error before `='
/tmp/ghc27506.hc:2689: parse error before `case'
/tmp/ghc27506.hc:2701: parse error before `else'
/tmp/ghc27506.hc:2706: parse error before `->'
/tmp/ghc27506.hc:2708: conflicting types for `__DISCARD__'
/var/tmp/ghc-2.04/fptools/ghc/driver/../includes/COptJumps.h:289:
previous declaration of `__DISCARD__'
/tmp/ghc27506.hc:2708: warning: data definition has no type or storage
class
/tmp/ghc27506.hc:2708: warning: initialization makes integer from
pointer without a cast
/tmp/ghc27506.hc:2708: initializer element is not constant
/tmp/ghc27506.hc:2708: warning: data definition has no type or storage
class^M
/tmp/ghc27506.hc:2708: parse error before `goto'
/tmp/ghc27506.hc:2711: parse error before `->'
/tmp/ghc27506.hc:2713: warning: data definition has no type or storage
class
/tmp/ghc27506.hc:2713: redefinition of `target'
/tmp/ghc27506.hc:2708: `target' previously defined here
/tmp/ghc27506.hc:2713: warning: initialization makes integer from
pointer without a cast
/tmp/ghc27506.hc:2713: initializer element is not constant
/tmp/ghc27506.hc:2713: warning: data definition has no type or storage
class
/tmp/ghc27506.hc:2713: parse error before `goto'
make[1]: *** [required/System.mr_o] Error 1
make: *** [all] Error 2 

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



ghc-2.04 compiling problems

1997-06-11 Thread Meurig Sage

I downloaded ghc-2.04 patch level 2. I then tried compiling it. I'm
using an i386-unknown-solaris2 machine. I get the error shown below.
I tried compiling using ghc-0.29. I was trying for profiled, concurrent
and concurrent profiled builds.

Cheers 
 Meurig

rm -f ghc/ArrBase.o ; if [ ! -d ghc/ArrBase ]; then mkdir ghc/ArrBase ;
else exit 0; fi; find ghc/ArrBase -name '*.o' -print | xargs rm -f
__rm_food;
../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
-split-objs -odir ghc/ArrBase   -H20m -c ghc/ArrBase.lhs -o
ghc/ArrBase.o -osuf o
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS array a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS (!) a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS (//) a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS accum a{~,Int,IPr} b{} c{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS accumArray a{~,Int,IPr} b{} c{} #-}
Warning: InitTime not found in stats file
Warning: InitElapsed not found in stats file
<>
ghc: module version changed to 1; reason: no old .hi file
/tmp/ghc27445.hc:953: fixed or forbidden register was spilled.
This may be due to a compiler bug or to impossible asm
statements or clauses.
make[2]: *** [ghc/ArrBase.o] Error 1
make[1]: *** [all] Error 2      

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



Bug in Concurrent Haskell

1997-05-15 Thread Meurig Sage

There's a bug in the signalQSemN function in the 
Semaphore module. (In versions ghc-0.29 through 2.03).

The following function blocks when x=y, but works when
y=x-1.

f x y = do
 qSem <- newQSemN 0
 forkIO (waitQSemN qSem y)
 threadDelay 1000
 signalQSemN qSem x
 return ()

The signalQSemN function needs a 1 line fix,
included below.

Cheers,
  Meurig

*** Semaphore.lhs.bug
 signalQSemN :: QSemN -> Int  -> IO ()
 signalQSemN (QSemN sem) n
  = takeMVar sem  >>= \ (avail,blocked) ->
free (avail+n) blocked>>= \ (avail',blocked') ->
putMVar sem (avail',blocked') >>
return ()
where
 free avail [] = return (avail,[])
 free avail ((req,block):blocked) =
! if avail > req then
putMVar block () >>
free (avail-req) blocked
  else
free avail blocked >>= \ (avail',blocked') ->
return (avail',(req,block):blocked')

*** Semaphore.lhs
 signalQSemN :: QSemN -> Int  -> IO ()
 signalQSemN (QSemN sem) n
  = takeMVar sem  >>= \ (avail,blocked) ->
free (avail+n) blocked>>= \ (avail',blocked') ->
putMVar sem (avail',blocked') >>
return ()
where
 free avail [] = return (avail,[])
 free avail ((req,block):blocked) =
! if avail >= req then
putMVar block () >>
free (avail-req) blocked
  else
free avail blocked >>= \ (avail',blocked') ->
return (avail',(req,block):blocked')





compiler bug in ghc-2.02

1997-04-22 Thread Meurig Sage

When compiling the following program, the compiler
crashed with a bug. This only happens when compiling
with -O.

--
module Test where
import GlaExts
test :: PrimIO ()
test = ioToPrimIO (putStr "bob") `seqPrimIO` test
--

--
ghc-2.02 -O -c test.hstest.hs:8: 
Warning: Possibly incomplete patterns
in a group of case alternatives beginning: 1 -> ...

*** Pattern-matching error within GHC!

This is a compiler bug; please report it to [EMAIL PROTECTED]

Fail: "coreSyn/CoreUtils.lhs", line 122: pattern-matching failed in case
-

I'm using ghc-2.02, with the i386-unknown-solaris2
pre-built distribution.

Cheers,
  Meurig



problem with syslib hbc and Time in ghc-2.02

1997-04-21 Thread Meurig Sage

I tried compiling a program using -syslib hbc, I
wanted Random.lhs, but I required the standard Time
library aswell. Unfortunately there's an interface
file for hbc called Time.hi, that overrides the
haskell 1.4 Time library. I assume this just requires
renaming of some of the hbc stuff.

Cheers,
  Meurig




mutually recursive modules

1997-04-19 Thread Meurig Sage

Hi,
 I've been playing around with mutually recursive modules
and getting nowhere. I tried the following two module 
program:

-
\begin{code}

module A where

import B

data A = A Int

findA :: A -> B -> Int
findA (A x) (B y) = x
\end{code}
-

-
\begin{code}

module B where
import A

data B = B Char

findB :: A -> B -> Int
findB (A x) (B y) = x
\end{code}
-

with the following Makefile

-
%.hi: %.o
@:

default all:: $(OBJS)

all :: $(OBJS)

SRCS = A.lhs B.lhs
OBJS = A.o B.o

all :: $(OBJS)

depend:: 
$(MKDEPENDHS) -- $(HC_OPTS) -- $(SRCS)

%.o: %.lhs
$(HC) $(HC_OPTS) -c $<

HC = ghc-2.02
MKDEPENDHS = mkdependHS
HC_OPTS = -recomp -cpp -hi-diffs $(EXTRA_HC_OPTS)
# DO NOT DELETE: Beginning of Haskell dependencies
A.o : A.lhs
A.o : ./B.hi
B.o : B.lhs
B.o : ./A.hi
# DO NOT DELETE: End of Haskell dependencies
-

I keep getting the following error message:

-
make: Circular A.hi <- A.o dependency dropped.
ghc-2.02 -recomp -cpp -hi-diffs  -c B.lhs
 
B.lhs:4: Could not find valid interface file for `A'


Compilation had errors
make: *** [B.o] Error 1
-

Is this a bug? If not, what am I doing wrong?

Cheers 
  Meurig



ghc-2.02 strangeness

1997-04-17 Thread Meurig Sage

Hi, I just downloaded the ghc-2.02 binaries for i386-unknown-solaris2 and installed 
them no problem. When I try compiling with them I get the following warning:

ghc-2.02: consistency error: major version not 36:
0134676624 n cc.storage.SMmark.hc.35.0..

The program compiled, however, and does run successfully. Should I be worried about 
this?
The program was just a simple Hello World program.

module Main where
main = putStrLn "hello world"

Cheers
 Meurig Sage



RE: Installing greencard

1997-04-15 Thread Meurig Sage


Hi,
yet more problems with green card.  I altered the settings but now get the following 
errors, when I try make boot. I can't see where the offending -f option is coming from.

Cheers
  Meurig

../mk/target.mk:1733: warning: overriding commands for target `show'
../mk/target.mk:738: warning: ignoring old commands for target `show'

===fptools== Recursively making `boot' in lib src ...
PWD = /usr/ghcstuff/fptools/green-card


==fptools== make boot;
 in /usr/ghcstuff/fptools/green-card/lib

../../mk/target.mk:1731: warning: overriding commands for target `show'
../../mk/target.mk:737: warning: ignoring old commands for target `show'
ghc-2.02 -f .depend\
 \
-- -fvia-C -cpp -fglasgow-exts -- StdDis.lhs
ghc-2.02: unrecognised option: -f
ghc-2.02: unrecognised option: --
ghc-2.02: unrecognised option: --

Usage: For basic information, try the `-help' option.
make: *** [depend] Error 3

==fptools== make boot;
 in /usr/ghcstuff/fptools/green-card/src

../../mk/target.mk:1733: warning: overriding commands for target `show'
../../mk/target.mk:738: warning: ignoring old commands for target `show'
ghc-2.02 -f .depend\
 \
-- -cpp -fglasgow-exts -H20m -fvia-C -- Data.lhs Frontend.lhs 
GHCBackend.lhs GetOpt.lhs GreenCard.lhs HUGSBackend.lhs Package.lhs Pretty.lhs 
Util.lhs Scan.hs Lex.hs Parse.hs
ghc-2.02: unrecognised option: -f
ghc-2.02: unrecognised option: --
ghc-2.02: unrecognised option: --

Usage: For basic information, try the `-help' option.
make: *** [depend] Error 3
make: *** [boot] Error 2

--
From:   Sigbjorn Finne
Sent:   15 April 1997 07:58
To: Meurig Sage
Cc: 'Haskell Bugs'
Subject:Re: Installing greencard




Nothing :->, the cygwin32 port of GNU make is buggy when it comes to
dealing with sub-makes inheriting pieces of the environment. The
temporary workaround is just to manually copy the setting of HC down
into the lib/ and src/ directories inside green-card

Hope that helps,

--Sigbjorn





Installing greencard

1997-04-11 Thread Meurig Sage

Hi,
  I tried installing greencard on Windows NT and had problems. I picked up the basic 
binary bundle of ghc and that works ok. I then grabbed greencard. I followed the 
install file, running configure, and then trying make boot but got the following error 
message.

../../ghc/driver/ghc -M -optdep-f -optdep.depend -fvia-C -cpp -fglasgow-exts StdDis.lhs
make: ../../ghc/driver/ghc: Command not found

I uncommented HC in the makefile and set it to point to the installed version of 
ghc-2.02. (I used make in-place rather than the full install so it's in
HC=/usr/ghcstuff/fptools/bin/i386-unknown-cygwin32/ghc-2.02/ghc-2.02.)
So it shouldn't be trying to use the ghc in ../../ghc/driver. What am I doing wrong?

Meurig



ghc-0.29 -prof -concurrent

1997-02-28 Thread Meurig Sage

Having finally managed to get the profiled concurrent
version of ghc-0.29 compiled I discovered it was all
a wasted effort. (This was all on Solaris 2.5,
running on a Pentium.)

I tried compiling the following very simple program

import Concurrent

main = forkIO (putStr "hello\n")

with the command

ghc -fhaskell-1.3 -prof -concurrent main.hs

The program compiled with no problems but
when running it, there was immediately
a segmentation fault.

I got the following warning message a few times 
when compiling the profiled concurrent libraries
(libs_mr):

ghc: WARNING: splitting objects when profiling will 
*BREAK* if any _scc_s are present!

Could this have anything to do with it?

Cheers,
  Meurig Sage




Possible bug in Concurrent Haskell

1997-01-07 Thread Meurig Sage

There seems to be a bug in the Channel module from
ghc-0.29.

If I understand the description in the paper
correctly, dupChan should allow two readers to
both read all the data passed along a channel.
This doesn't work because of the way the getChan
function is written.

It takes the next value from the read end hole, but
does not put it back into the MVar to allow any other
reader to access it. 

The fix just requires one line: 

getChan :: Chan a -> IO a
getChan (Chan read write)
 = takeMVar read  >>= \ rend ->
   takeMVar rend  >>= \ res@(ChItem val new_rend) ->
***putMVar rend res >>
   putMVar read new_rend  >>
   return val

Cheers,
 Meurig