bug report

1997-04-04 Thread Marc van Dongen
Dear all, I would like to report a bug in ghc-2.02. In ghc-0.29 and ghc-2.01 the program attached below compiles fine. The 2.02 version of ghc fails. Is there any chance this bug will be fixed in near future? Regards, Marc van Dongen

bug report

1996-12-04 Thread Marc van Dongen
sible' happened): Unexpected Dict or ForAll in occurCheck Please report it as a compiler bug to [EMAIL PROTECTED] * Whereas > module A( B ) where > data B = C a compiles fine. Is this valid Haskell? Regards, Marc van Dongen [EMAIL PROTECTED]

Big heap for a small program

1997-04-09 Thread Marc van Dongen
I just wanted to report that the erroneous and tiny program added below can not be compiled within 6MB of heap (Admitted it can be compiled with a bigger heap). It was part of a bigger program that could not be compiled within 20MB of heap. Regards, Marc van Dongen [EMAIL PROTECTED

Happy bug report

1997-04-19 Thread Marc van Dongen
> { > happyError :: Int -> [Token] -> a > happyError i'' _ > = error errstr > where errstr = "This code fragment forces Happy to return with" ++ > "the following error message:\n\n" ++ > "Fail: Lexical Error: No closing '}' in code segment\n\n" ++ >

another one

1997-05-30 Thread Marc van Dongen
I cannot think of any reason why compiling the following two programs should give different results. Maybe some deep reason? Anyway, the following compiles fine: *** > module Rings( Group ) where > import qualif

bug report

1997-05-31 Thread Marc van Dongen
Hi, While I was constructing an example for ghc-users, I created the following program which crashed ghc-2.03. > module Tmp( g ) where > data AB p q = A > | B p q > g :: (Ord p,Ord q) => (AB p q) -> Bool > g (B _ _) > = g A tmp.lhs:6: Warning: Possibly incomplete patter

tcLookupTyVar error (Similar as last one? Don't know.)

1997-05-31 Thread Marc van Dongen
s helps. Regards, Marc van Dongen > module Rings( Group, Ring ) where > import qualified Prelude( Ord(..), Eq(..), Num(..) ) > import Prelude hiding( Ord(..), Eq(..), Num(..), MonadZero( zero ) ) > cl

Correction

1997-06-02 Thread Marc van Dongen
(Group a) => a -> a -> a Group a => added > multiply a b > = case (compare a zero) of > EQ -> zero > LT -> zero - (multiply (zero - a) b) > GT -> case compare

profiling

1997-06-15 Thread Marc van Dongen
Hi all, I have noticed that profiling in ghc-2.03 in combination with -O or -O2 is not possible because of some problems at the linking stage. Also it turns out that profiling combined with tracing results in programs which don't output any trace at all. Are the problems related to profiling an

-fshow-specialisations

1997-06-15 Thread Marc van Dongen
This does not work in ghc-2.03. ghc-2.03: unrecognised option: -fshow-specialisations Hope this helps. Regards, Marc van Dongen

bug report

1997-06-26 Thread Marc van Dongen
I would like to report the following bug in ghc-2.04. Profiling and optimizing with -O2 (I have not and will not try -O) leads to errors like this at link-time: CC_mkZubalancedZ92Z92Z92Zq_struct Blah1.o CC_DICTs_struct Blah2.o CC_mkZubalancedZ92Zq_struct Blah3.o CC_

bug report

1997-07-20 Thread Marc van Dongen
s a) => Read (L a) where > readsPrec _ _ = [(L [],[])] > buggy :: (Class a) => (L a) -> (L a) > buggy omega > = g omega 1 > g :: (Class a) => (L a) -> a -> (L a) > g omega one > = omega I had expected an overloading error because of the use of ``1'' in the definition for ``buggy''. Hope this helps. Regards, Marc van Dongen

bug report

1997-05-30 Thread Marc van Dongen
If my memory serves me right, I haven't seen this one in ghc-2.03: *** Pattern-matching error within GHC! This is a compiler bug; please report it to [EMAIL PROTECTED] Fail: "typecheck/Unify.lhs", line 60: incomplete pattern(s) to match in function "unifyTauTyLists" Caused by the followin

bugg report (profiling again)

1997-07-16 Thread Marc van Dongen
Module3.o CC_nubZ92Zq_struct Module4.o ld: fatal: Symbol referencing errors. No output written to ModuleMain Compiling without profiling and -O2 or compiling with -O2 but without profiling produces no errors. Regards, Marc van Dongen

bug report

1997-08-01 Thread Marc van Dongen
: `(first triple) PrelBase.== (PrelTup.fst triple)' Hope this helps, Marc van Dongen [EMAIL PROTECTED]

bugg report

1997-08-24 Thread Marc van Dongen
Hi there, I would like to report the following bugs (ghc 2.0498:). ## 1 ### The following program: > module Main( main ) where > main = putStr (seq bot "1\n") >> >return () > where bot = error

bug report

1997-05-29 Thread Marc van Dongen
Compiling the code fragment appended at the end of this message, ghc-2.03 fails with the following output: Glasgow Haskell Compiler, version 2.03, for Haskell 1.4 panic! (the `impossible' happened): tcLookupTyVar:a_r6v Please report it as a compiler bug to [EMAIL PROTECTED] H

profiling

1997-09-29 Thread Marc van Dongen
-names out of the profiling package? I have looked at the .hp files, but the information does not seem to be available at that level. Any help would be greatly appreciated. Regards, Marc van Dongen [EMAIL PROTECTED]

bug report

1997-11-28 Thread Marc van Dongen=
/usr/local/ghc-2.09/lib/libHS.a(GHCmain__7.o) I have not used the function getBufferMode in my source. I do have a hSetBuffering. Any suggestions how to get around this? Thanks in advance, Marc van Dongen

symbol referencing error (profiling 2.09)

1997-12-08 Thread Marc van Dongen=
/usr/local/ghc-2.09/lib/libHS_p.a(GHCmain.p_o) ld: fatal: Symbol referencing errors. No output written to Groebner Hope this helps. Marc van Dongen Marc van Dongen, Computer Science Dept | phone: +353 21 903083 National

happy bug

1998-01-21 Thread Marc van Dongen=
py generates .. (let a = 1 b = 2 .. Which isn't proper Haskell. Regards, Marc van Dongen

space leak

1998-01-28 Thread Marc van Dongen=
he last line of this program was changed to > where str = (show.concat) > [let fx = f x in [fx y | y <- [1..big]] | x <- [1..big]] Hope this helps. Regards, Marc van Dongen

bug report

1998-01-30 Thread Marc van Dongen=
Dear all, While compiling some stuff I came across the following: compiling with -O did failed without any error message at all. compiling with -O2 succeeded ? Any idea what could have caused it? I can tell you how to reproduce this if wanted. Regards, Marc

is this a bug?

1998-01-30 Thread Marc van Dongen=
Hi there, While using mkdependHS, I am getting errors because the tool can not find .hi files for modules which are imported from a library in some other directory than the one I'm making in. Is this an error, and if not, how do I solve this? Thanks in advance, Marc van Dongen

Re: is this a bug? (fwd)

1998-01-30 Thread Marc van Dongen=
: Hi there, : : : : While using mkdependHS, I am getting errors because the : tool can not find .hi files for modules which are imported : from a library in some other directory than the one I'm : making in. : : Is this an error, and if not, how do I solve this? : This is embarrassing. As so

bug report

1998-01-31 Thread Marc van Dongen=
with different input caused a segmentation fault after more than 2000 seconds. In both cases I was running with a +RTS -PT -RTS run-time option. Regards, Marc van Dongen

bug report

1998-02-05 Thread Marc van Dongen=
The following won't compile under 3.00 > data Blah = Blah > type Tuple = (Blah,Int) > instance Show Tuple where > showsPrec _ _ _ > = error [] No instance for: `Show Blah' arising from use of `PrelBase.$mshowList', at tmp.lhs:8 I know that instances of classes shouldn't be ty

bug report

1998-02-05 Thread Marc van Dongen=
{-rHG-} (Pol.Polynomial{-rHB-} $x0_ts1Kze $x1_ts1Kzd)) PrelBase.Integer{-3g-} If more details are needed please call. Regards, Marc van dongen

instance again

1998-02-05 Thread Marc van Dongen=
ce Ord Blah > instance Read Blah > instance Show Blah Adding the previous 4 dummy instance declarations makes this fragment to become acceptable to ghc-3.00. > instance Show Tuple where > showsPrec _ _ _ > = error [] Regards, Marc van Dongen

bug report 3.00

1998-02-06 Thread Marc van Dongen=
aven't got a clue of what causes it. Feel free to contact me for more information. Regards, Marc van Dongen ________ Marc van Dongen, Computer Science Dept | phone: +353 21 903083 University College Cork, NUIC

Re: ghc-3.00-linux bug in linking

1998-02-11 Thread Marc van Dongen=
spj: : Sergey, Marc : : I've had a look at your Docon thing. It really is Sergey's thing. He deserves all the credit. [snip] Cheers, Marc

Is this a bug?

1998-03-01 Thread Marc van Dongen=
Hi there, I suspect the program included below is incorrect. Nevertheless it compiles fine under ghc-3.01 patchlevel 0. > module Main( main ) where > import List( genericLength ) > main = putStr (show integral) >> >putStr "\n">> >return () > where integral = gen

Re: Is this a bug?

1998-03-01 Thread Marc van Dongen=
[snip] : > > module Main( main ) where : > > import List( genericLength ) : > > main = putStr (show integral) >> : > >putStr "\n">> : > >return () : > > where integral = genericLength [] [snip] : This is a legal Haskell program. The (ambiguous) type of `integra

quotes deleted in error messages

1998-03-30 Thread Marc van Dongen=
Hello there, While compiling some source code of mine, containing the following lines (line numbers included): 321 322 > minCycleLength :: Vertex -> (MarcMap Vertex (MarcMap Vertex v)) -> Maybe Int 323 > minCycleLength v g 324 > = mcl ws g'' 325 > where ws = mapDom (rdMap g v) 326 >

``bug report''

1998-06-03 Thread Marc van Dongen
Hi there, In ghc-3.02 the following program compiles fine. > module Main( main ) where > f :: String -> Int > f "=<" = 0 > f "=" = 0 > g :: [Char] -> Int > g ['=','<'] = 0 > g ['='] = 0 > main = return () However, for ``f'' the following is reported. tmp.lhs:4: Pattern match(es) a

reader/ReadPrefix.lhs:159: Non-exhaustive patterns in case

1998-06-06 Thread Marc van Dongen
Hi there, While trying to compile the following eroneous program > module Buggy( buggy ) where > buggy = _ with ghc-3.02, ghc decided to go down with the following error message: reader/ReadPrefix.lhs:159: Non-exhaustive patterns in case Hope this helps, Marc

tcLookupGlobalValue

1998-07-23 Thread Marc van Dongen
Hi there, I would like to report the following. After splitting up one module in two seperate modules in two different files, I ended up with something as follows: swift> more A.lhs > module A( a ) where > a = 1 swift> more B.lhs > module A( b ) where > import A( a ) > b = a + a The compilat

stranal/SaAbsInt.lhs:668: Non-exhaustive patterns in function `absApply'

1998-08-01 Thread Marc van Dongen
Hi there, > module F( f ) where > class C a b where > f :: a -> b -> b > instance C Bool b where > f a b = if a then b else b > instance C (IO Bool) (IO b) where > f a b = a >>= \bool -> f bool b Leads to a ghc-3.02 crash: stranal/SaAbsInt.lhs:668: Non-exhaustive patterns in function `a

bug report 4.00

1998-11-17 Thread Marc van Dongen
Hi there, While compiling some stuff with 4.00 I get the following output before compilation stops. [snip] GNU CPP version 2.7.2 (sparc) #include "..." search starts here: #include <...> search starts here: . /usr/local/ghc-4.00/lib/ghc-4.00/includes /usr/local/ghc-4.00/lib/ghc-4.00/include

bug report

1998-11-17 Thread Marc van Dongen
Hi there, I can't see why the following will not compile with 3.02 > module Main( main ) where > data A a = A (a,a) > instance (Show a,Ord a) => Num (a,a) where > (+) a a' = a > instance (Show a,Ord a) => Eq (A a) where > (==) a a' = True > instance Show (A String) where > showsPrec

`__ap_9_upd_info' undeclared

1998-12-02 Thread Marc van Dongen
went wrong. If you need more info to know what is going on, please let me know and I may give it a shot to isolate the problem. Regards, Marc van Dongen ** ghc-4.00 -c Filnam.lhs -recomp -v -fglasgow-exts -cpp -hi-diffs -syslib

Pattern match(es) overlapped (again)

1998-12-15 Thread Marc van Dongen
Hi there, This is ghc-4.01 I have not seen an instance of such a message for non-overlapping patterns for non-string types. As part of a where clause I have (modulo renaming) two equations of the following form: f Pat1 p2 p3 p4 = rhs1 f Pat2 p2 p3 p4 = rhs2 where Pat1 and Pat2 a

Overlapping Patterns (false alarm)

1998-12-15 Thread Marc van Dongen
Hello again, Sorry about my previous ``report'' on overlapping patterns. I overlooked the fact that the first ``ground'' instance appearing in the function definition was, in fact, a variable. GHC really works! Regards, Marc

kind mismatch ($)

1999-01-04 Thread Marc van Dongen
ng quotes (` and ') around parts of its messages. This becomes *very* confusing when the last part of the message consists of an identifier suffixed by a one or more quote symbols. Regards, Marc van Dongen

Type-inference using functions from different modules

1999-04-06 Thread Marc van Dongen
ile. It seems as if something goes wrong when exporting functions across different modules. Regards, Marc van Dongen

Re^2: Extra output lines from trace.

1999-04-09 Thread Marc van Dongen
Hi there, This is related to at least two earlier messages in this forum which sadly enough I only noticed today. It probably is a feature that since then trace doesn't print Trace on/Trace off anymore. Is there any reason for not doing this anymore? In my opinion it makes tracing very awkward.

Proposal for error message improvement

1999-04-15 Thread Marc van Dongen
the problem. However, the more equations there are in the definition of a function, the more difficult I have found it to locate the cause of errors resulting in error messages as the one above. Would it be possible to provide an explanation as to what could have caused such errors? Regards, Marc van Dongen

Re: Integer -> Int conversion

1999-06-23 Thread Marc van Dongen
mult1 = (1-maxBound)*(1-maxBound) >mult2 = (maxBound-1)*(maxBound-1) outputs: According to ghc-4.02 (1-maxBound)^2 = 4 According to ghc-4.02 (maxBound-1)^2 = 4 Mod maxBound the result of both multiplication should have been 1. Maybe it is better to rely on Integers. Regards, Marc van Dongen

bug with trace

1999-07-01 Thread Marc van Dongen
eras it should have output: 0 1 Fail: Prelude.tail: empty list Regards, Marc van Dongen

Manual Pages Unboxed Values

1999-08-01 Thread Marc van Dongen
Integer = S# Int#-- small integers | J# Int# ByteArray# -- large integers Regards, Marc van Dongen

ghc-4.04 (-fddump-rules and -fddump-simpl-stats don't work)

1999-08-01 Thread Marc van Dongen
-O2? Regards, Marc van Dongen _______ Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Internal Happy Error

1999-08-01 Thread Marc van Dongen
ormIO $ >_casm_ gcdSBSZh a sb b >>= \g -> > case g of (I# g) -> return (S# g) Hope that helps. Regards, Marc van Dongen

Re: ghc from CVS (1999/07/31) throws core...

1999-08-02 Thread Marc van Dongen
c Exception (core dumped) Regards, Marc van Dongen

Internal Happy Error (another one)

1999-08-02 Thread Marc van Dongen
Hi there, ghc-4.04's parser does not seem to like expressions of the following kind: case a of (#I a) -> and blah (# sa, a, #) Upon using these expressions it dies due to an internal Happy error. Hope this helps, Marc van Dongen

Re: 4.04 Sparc dist

1999-08-06 Thread Marc van Dongen
: I've put up a new sparc-sun-solaris2 build of 4.04 on the web site. This : one at least has no strange empty modules in libHS.a. I have no idea what : went wrong with the first one, but we've been having some strange NFS : corruptions here so I have my suspicions. : : Let me know if there are

make depend

1999-09-09 Thread Marc van Dongen
Hi There, When I noticed that my mkdependHS didn't work any more I noticed that the release notes for ghc-4.04 mentioned that this program had become obsolete and that ghc-4.04 -M should be used instead. The problem I have with ghc-4.04 -M is that is seems to be *very* reluctant to generate de

Re: make depend

1999-09-09 Thread Marc van Dongen
in the Makefile. I think I'll wait until I am refered to some form of documentation. Thanks again, Marc van Dongen

Re: make depend

1999-09-09 Thread Marc van Dongen
or more. That's interesting. I hadn't noticed that section. I looked at Section 2 (Using GHC/command line options) which doesn't make any reference to the -M flag. I'll try again. Thanks. Regards, Marc van Dongen

Segmentation Fault (After installing 2.95.2)

1999-12-16 Thread Marc van Dongen
sem to run fine.) Regards, Marc van Dongen ___ Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Bug Report: Export List in Module

2000-01-22 Thread Marc van Dongen
Hello, I just found out that module definitions of the following kind > module Commas( , , ) where are accepted by ghc. One comma also seems to be fine. Regards, Marc van Dongen

CVS make all failed: RegAllocInfo

2000-01-31 Thread Marc van Dongen
same from cvs yesterday. After updating today this failed. Any suggestions on how to fix this will be greatly appreciated. Thanks in advance. Marc van Dongen *** log *** ===fpt

cvs: make all fails (RegAllocInfo does not export findreservedRegs)

2000-02-01 Thread Marc van Dongen
Hello there, CVS: make all fails with the following message: AsmCodeGen.lhs:24: Module `RegAllocInfo' does not export `findReservedRegs' Compilation had errors make[2]: *** [nativeGen/AsmCodeGen.o] Error 1 make[1]: *** [all] Error 1 make: *** [all] Error 1 Regards, Marc

CVS: make all: [MatchPS.o] Segmentation Fault (core dumped)

2000-02-02 Thread Marc van Dongen
required. Regards, Marc van Dongen

Interface file problem

2000-02-02 Thread Marc van Dongen
ow to fix this? Thanks in advance. Regards, Marc van Dongen

cvs 4.07 arithmetic errors in Integer arithmetic

2000-02-28 Thread Marc van Dongen
against applying the same fix for 4.06? Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

cvs: MachCode (undeclared functions)

2000-03-01 Thread Marc van Dongen
Hi there, Make all fails due to the fact that some functions in nativeGen/MachCode are undeclared. Log appended. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland

cvs: Profiling.c:462: strucuture has no member named `emitted'

2000-03-01 Thread Marc van Dongen
Hi there, I just updated cvs and now make fails because of a Profiling.c:462: strucuture has no member named `emitted' thingy. Log appended. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 9

cvs: make boot fails: mkdependHS-inplace: can't open directory haxml/lib

2000-03-01 Thread Marc van Dongen
Hello again, When carrying out a make boot with cvs this caused a problem because of the following: mkdependHS-inplace: can't open directory haxml/lib I have appended a log. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork,

Re: make boot fails: mkdependHS-inplace: can't open directory hax ml/lib

2000-03-01 Thread &#x27;Marc van Dongen'
yesterday. Thanks. Mike Gunter also pointed me in this right direction. Regards, Marc -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

cvs: Profiling.c:462: parse error before `<'

2000-03-02 Thread Marc van Dongen
Hello again, When making cvs it halts because of a Profiling.c:462: parse error before `<' I have appended a log. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork,

Re: Profiling.c:462: parse error before `<'

2000-03-02 Thread &#x27;Marc van Dongen'
7;s problem by hand, : hence the conflict), then just remove Profiling.c and cvs update to recover : the stock version. Thanks, that solved that problem. Now I get a:-( StixPrim.lhs:6: Could not find valid [boot] interface file `OrdList' Any suggestions? Log appended. Regards, Marc van Don

cvs built ghc creates segmentation fault generating binaries

2000-03-03 Thread Marc van Dongen
thmetic to be the cause of the problem. I'll try to locate the error and let you know of my findings. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 903578 University College Cork, NUIC | Fax: +353 21 903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Re: -O2 == crash

2000-03-09 Thread Marc van Dongen
ll crashes. With -O it does not. : With -O2-for-C it does not. Hi Macin, I installed gcc-2.95 some months ago and downgraded to 2.8.1 because I couldn't get it running. gcc-2.8.1 seemed to work fine (until a few days ago). Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone:

FastString.lhs:629: parse error on input `#'

2000-03-13 Thread Marc van Dongen
gards, Marc van Dongen -- ===fptools== Recursively making `all' in glafp-utils ghc hslibs ... PWD = /newdisk/dongen/c

Re: FastString.lhs:629: parse error on input `#'

2000-03-13 Thread Marc van Dongen
George Russell ([EMAIL PROTECTED]) wrote: : Marc van Dongen wrote: [error at line 629] : Odd, because I get (from the anon-cvs repository) : : /usr/local/pub-bkb/ghc/ghc-latest/bin/ghc -cpp -fglasgow-exts -Rghc-timing -I. :-IcodeGen -InativeGen -Iparser

cvs: make all -> error PackedString.lhs

2000-03-12 Thread Marc van Dongen
e_array len' Compilation had errors make[2]: *** [PackedString.o] Error 1 make[1]: *** [all] Error 1 make: *** [all] Error 1 Log appended. Regards, Marc van Dongen

Re: cvs: make all -> error PackedString.lhs

2000-03-12 Thread Marc van Dongen
Sven Panne ([EMAIL PROTECTED]) wrote: : Marc van Dongen wrote: : > Just to let jou know. I just updated and tried to rebuild : > ghc from cvs. I then got: : > : > PackedString -c PackedString.lhs -o PackedString.o -osuf o : > [...] : : I've already fixed that one (and

Re: Enum instance for Ratio

2000-03-09 Thread Marc van Dongen
George Russell ([EMAIL PROTECTED]) wrote: : Marc van Dongen wrote: : > Wouldn't that make Enum depend on Ord? : > Doesn't seem to make sense if classes are : > enumerable but not comparable. Of course above I should have said orderable in stead of comparable. : What examples

Re: Enum instance for Ratio

2000-03-09 Thread Marc van Dongen
George Russell ([EMAIL PROTECTED]) wrote: : A logical definition of Enum (to me wearing a mathematical hat) : would be : : succ x = min { y | y > x} : Wouldn't that make Enum depend on Ord? Doesn't seem to make sense if classes are enumerable but not comparable. Regards, Marc

cvs: make all -> SocketPrim error

2000-03-15 Thread Marc van Dongen
/parsec make[2]: *** [SocketPrim.o] Error 1 make[1]: *** [all] Error 1 make: *** [all] Error 1 Just to let you know. Log appended. Regards, Marc van Dongen

SocketPrim (more info)

2000-03-15 Thread Marc van Dongen
&& ./configure \ && make boot \ && make all Regards, Marc van Dongen

Re: Recent Sparc breakage

2000-03-16 Thread &#x27;Marc van Dongen'
me for further info:. Regards, Marc van Dongen

Buglett: error message

2000-04-15 Thread Marc van Dongen
Hello all, One small buglet in ghc-4.06: When trying to compile one of my programs the following was generated as part of an error message: where a2s = ! arr The last line should have been: a2s = (!) arr That's all. Regards, Marc van D

segmentation fault: Solved

2000-04-26 Thread Marc van Dongen
Hi Simons, The problem I reported a few days ago seems to be solved. Furthermore ghc-4.07 seems to be a *lot* faster in compiling thingies. I haven't tested the speed of the executables yet. Great work. Regards, Marc -- Marc van Dongen, CS Dept | phone: +353 21 4903578 Unive

Re: ghc -v always makes gcc-2.95.1 dump core?

2000-05-13 Thread Marc van Dongen
Marcin 'Qrczak' Kowalczyk ([EMAIL PROTECTED]) wrote: [ghc-2.95 problem] Hi Marcin, I had problems with ghc-2.95 as well and decided to downgrade to 2.8.1 Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:

mkdependHS (proposal for improvement)

2000-06-01 Thread Marc van Dongen
Hi there, I don't know if this is a known problem. The ``problem'' with mkdependHS is when it is used in conjunction with happy. The imports in the .ly file are not recognised and one has to rebuild sources by hand. I am surprised I never noticed this before and it isn't a big problem. Just a t

mkdependHS (again)

2000-06-01 Thread Marc van Dongen
Hello again, Please ignore my previous email. When used properly mkdependHS *does* indeed recognise dependencies in happy input files. The reason why it didn't work for me was because I didn't have a *.ly argument in my makefile. Sorry for the confusion. Regards, Marc

Integer arithmetic broken (again)

2000-06-03 Thread Marc van Dongen
free to contact me for further information. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Re: Integer arithmetic broken (again)

2000-06-04 Thread Marc van Dongen
Sven Panne ([EMAIL PROTECTED]) wrote: : [EMAIL PROTECTED] might be the more appropriate list. A reader of that list asked me explicitly not to send it to that list because he thought it wasn't appropriate to sent cvs-bug messages to that list:-) I'll send further error messages to cvs-ghc in th

ghc-4.08 core dumps: probably parenthesis related

2000-07-05 Thread Marc van Dongen
heses is not ok. Hope this helps. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Variable not in scope: Incorrect parsing

2000-08-11 Thread Marc van Dongen
ere the 5 refers to the last line containing b. Hope this helps. Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

Bug report: mkPrimReturnCode: Upd tpl4{-c9vM-}

2000-08-13 Thread Marc van Dongen
The annotations were added in a file containing type and data definitions only. The compilation of that file went fine. The compilation of another one depending on the types went wrong:-( I have attached a log. Let me know if you need some more info. Regards, Marc van Dongen -- Mar

Re: 'undefined reference to `_imp__Addr_zdfNumAddrOff_closure' (? ????????)

2000-09-27 Thread Marc van Dongen
f 32. Regards, Marc van Dongen