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

Re: Problems with GHC-4.08.1 on Windows 2000 Professional

2001-01-30 Thread Meurig Sage
Hi I had the same problem. The problem is with one of your cygwin libraries. Reuben Thomas sent me this reply: - You probably need to change the mingw package: if its date is 200012xx, try downgrading to 200011xx. This recommendation also applies to Janna Khegai's message.

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 = dochan - newChanch - dupChan chanwriteChan chan "done"x - readChan chany - readChan chprnt ("Got "++x ++" "++y) Now if I remember correctly this should print "Got done done". Instead it exits

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

Re: FranTk: how to justify a widget collection?

2000-09-05 Thread Meurig Sage
Hi Regarding the nabove question, if you use "packAnchor W" then it should align the widgets to the left. If this doesn't work then there is a bug. Let me know and I'll fix it. As far as giving configuration options to composite widgets. FranTk will eventually allow this, but does not do so at

Re: Win 32 GUI for GHC

2000-07-18 Thread Meurig Sage
of TclHaskell, which uses concepts from Conal Elliott's Functional Reactive Animation to provide a more declarative interface for GUI programming. http://www.dcs.gla.ac.uk/~meurig/TclHaskell/ http://www.haskell.org/FranTk/ If you have any questions about either let me know. Meurig Sage - Original

Re: GUI programming

2000-01-20 Thread Meurig Sage
Hi, I'm the developer and keeper of FranTk and TclHaskell. I note Simon PJ suggested you have a look at FranTk. It's the more powerful of the two and provides good support for structuring programs. (It's built on top of TclHaskell.) I spent the summer working with the GHC group on it.

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,

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

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

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

Re: Announce: frantk

1999-10-04 Thread Meurig Sage
then it is definitely a path problem. Try adding the TclHaskellSrc directory to your path. Hope this works, let me know how you get on. Meurig Meurig Sage wrote: Announce: FranTk I can't get franTk running under Win95. It fails with: Error while importing DLL "c:\t\TclHaskellSrc\TclPrim.dll" This

Announce: frantk

1999-09-17 Thread Meurig Sage
ug reports to: Meurig Sage, [EMAIL PROTECTED] Download FranTk from http://www.haskell.org/FranTk/

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

Announce: TclHaskell

1999-08-12 Thread Meurig Sage
of TclHaskell. There is a user manual, and demos directory, with a full range of examples. Send bug reports to: Meurig Sage, [EMAIL PROTECTED] (I'll be away for the next fortnight and will only be looking at my email intermittently). The TclHaskell web site is at: http://www.dcs.gla.ac.uk/~meurig

RE: Which GUI on X11R6 ?

1999-08-02 Thread Meurig Sage
a new release of it out in the next few days that works with hugs98 and ghc-4.04. Meurig Sage -- previous mail sent 20 July 1999 --- Hi, I am indeed working on an improved version of TclHaskell. I'll be providing an initial release within a few weeks. (Hopefully by the end of this month

RE: Looking for TkHaskell

1999-07-20 Thread Meurig Sage
/TkHaskell.html but I believe Meurig Sage is working on a much improved version as we speak. I've used TclHaskell a bit and quite like it, but it does have a few rough edges. Chris Dornan is no longer maintaining it, unfortunately.

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-11 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

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'

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

Segmentation faults with ghc-4.02 code

1999-02-19 Thread Meurig Sage
} etc. are irrelevant for tcl. ---- */ void primSetVar(char *varname, char *inp) { if (tcl_debug) { fprintf(stderr, "set %s %s\n", varname, inp); } Tcl_SetVar(interp, varname, inp, TCL_GLOBAL_ONLY); } -- Meurig Sage Dept of Computing Science University of Glasgow http://www.dcs.gla.ac.uk/~meurig mailto:[EMAIL PROTECTED]

Problem with ghc-4.02

1999-02-11 Thread Meurig Sage
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: MonadZero (concluded)

1998-11-06 Thread Meurig Sage
to mplus eg plusMb :: Maybe a - Maybe a - Maybe a I use this sort of thing a lot. I think I'd prefer MonadPlus to stay though. Keep it in the Monad library? Meurig -- Meurig Sage Dept of Computing Science University of Glasgow http://www.dcs.gla.ac.uk/~meurig mailto:[EMAIL PROTECTED]

Re: Standard Haskell and Monad Comprehensions

1997-08-27 Thread Meurig Sage
ERY useful having the do syntax, as it has made the sequential part of the functional programs easy to explain. -- 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
-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

labelled fields in ghc-2.04

1997-06-12 Thread Meurig Sage
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]

Another ghc-2.04 compiling problem

1997-06-12 Thread Meurig Sage
-- 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
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

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