Re: bug report

1996-12-05 Thread Simon L Peyton Jones



| > module A( B ) where
| 
| > data B = C a

This isn't legal Haskell: data constructors can't mention 
type variables not bound on the left hand side.  This would be legal

> data B a = C a

But it still shouldn't crash the compiler!

Thanks for the bug report

Simon



Re: bug report

1997-05-30 Thread Simon L Peyton Jones


Good report!  The contexts on the signatures in a mutually recursive group
must be the same (i.e. unifiable), but GHC wasn't being careful enough..
here they aren't even the same length.  Embarassing, but easily fixed.

Simon

| From: Marc van Dongen <[EMAIL PROTECTED]>
| Date: Fri, 30 May 1997 12:14:47 +0100 (BST)
| 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]
|  k.
|   Fail: "typecheck/Unify.lhs", line 60: incomplete pattern(s) to match in funct
|  ion "unifyTauTyLists"
| 
| Caused by the following faulty program:
| 
| > module F( f ) where
| 
| > f :: (Ord c) => c -> c
| > f c = g c
| 
| > g :: c -> c
| > g c = c
| >   where p = foldr (f c) [] []
| 
| Regards,
| 
| 
| 
| Marc



Re: bug report

1997-06-17 Thread Simon L Peyton Jones



Marc,

GHC 2.04 correctly says

Main.hs:17: Ambiguous overloading
arising from use of `g' at Main.hs:23
`PrelBase.Ord' `p{-a17v-}'
When checking signature(s) for: `g'

| From: Marc van Dongen <[EMAIL PROTECTED]>
| Date: Sat, 31 May 1997 14:35:40 +0100 (BST)
| 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 patterns in the definition of function `g'
| 
|   zonkIdOcc: g_aoQ
| 
|   panic! (the `impossible' happened):
|   lookupBindC:no info!
|   for: g_aoQ
|   (probably: data dependencies broken by an optimisation pass)
|   static binds for:
|   Tmp.$d1{-rmM,x-}
|   local binds for:
| 
| Two seconds later, my system crashed. I assume ghc-2.03 did not cause this :-)
| 
| 
| Regards,
| 
| 
| Marc



Re: bug report

1997-06-12 Thread Sigbjorn Finne

Marc van Dongen writes:
> 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 patterns in the definition of function `g'
> 
>   zonkIdOcc: g_aoQ
> 
>   panic! (the `impossible' happened):
>   lookupBindC:no info!
>   for: g_aoQ
>   (probably: data dependencies broken by an optimisation pass)
>   static binds for:
>   Tmp.$d1{-rmM,x-}
>   local binds for:
> 

Hi,

sorry for being a bit slow - this panic has been cured in ghc-2.04,
you'll now instead get a type error about overloading being ambiguous.

I notice that the Hugs type checker accepts `g' above, but I'll leave
it to others to pass judgement on what is the right behaviour.

--Sigbjorn



Re: bug report

1997-08-01 Thread Sigbjorn Finne


Thanks, misleading error message this - the pattern guard extension
allows you to write qualifiers a la list comprehensions on the
left-hand side. 

The front-end simply re-uses the implementation for list
comprehensions to do this, hence the error messages may still be a bit
skewed toward list comprehensions.

--Sigbjorn

Marc van Dongen writes:
> Hi there,
> 
> 
> ghc-2.0498, complains about list-comprehensions
> when compiling the following. There's probably some
> code-transformation going on here.
> 
> > module Strange( strange ) where
> 
> > strange :: (a,a,a) -> a
> > strange triple
> >   | (first triple) == (fst triple) = first triple
> 
> > first :: (a,b,c) -> a
> > first (a,b,c)
> >   = a
> 
> Stange.lhs:5: Couldn't match the type
>`PrelTup.(,,) tazz' against `PrelTup.(,)'
> Expected: `(tazz, tazz, tazz)'
> Inferred: `(tazz, tazN)'
> In a list-comprehension qualifer:
> `(first triple) PrelBase.== (PrelTup.fst triple)'
> 
> Hope this helps,
> 
> 
> 
> 
> Marc van Dongen
> [EMAIL PROTECTED]



Re: bug report

1997-08-18 Thread Simon L Peyton Jones

 
> > > module Strange( strange ) where
> > 
> > > strange :: (a,a,a) -> a
> > > strange triple
> > >   | (first triple) == (fst triple) = first triple
> > 
> > > first :: (a,b,c) -> a
> > > first (a,b,c)
> > >   = a
> > 
> > Stange.lhs:5: Couldn't match the type
> >`PrelTup.(,,) tazz' against `PrelTup.(,)'
> > Expected: `(tazz, tazz, tazz)'
> > Inferred: `(tazz, tazN)'
> > In a list-comprehension qualifer:


Thanks for the report.   The error message now says "In a guard:". (In the
next release.)

Simon





Re: bug report

1997-05-30 Thread Simon L Peyton Jones


Marc you are outstanding at winkling out these bugs.
This is an erroneous program because 0 doesn't have type (forall a.a),
but it should not crash the compiler.

I've fixed it in 2.04.

Simon

| From: Marc van Dongen <[EMAIL PROTECTED]>
| Date: Thu, 29 May 1997 22:38:32 +0100 (BST)
| 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

| > module Group( Group ) where
| 
| > import qualified Prelude( Num(..) )
| > import Prelude hiding ( Num(..) )
| 
| > class Group a where
| >   fromInteger :: Integer -> a
| >   (-) :: a -> a -> a
| >   negate  :: a -> a
| >   negate p
| > = (0::a) - p
| 



Re: bug report

1998-01-30 Thread Simon Marlow

Marc van Dongen= <[EMAIL PROTECTED]> writes:

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

No idea, could you provide a test case please?

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: bug report

1998-02-01 Thread Simon Marlow

Marc van Dongen= <[EMAIL PROTECTED]> writes:

> One of my programs caused a:
> 
> Entered Forward_Ref 7f0928: Should never occur!

We've heard of this one before, but haven't actually been able to
reproduce it.  Anyway, the upshot is that we're rewriting the
profiling support for the new run-time system, so we're not going to
expend a great deal of effort on fixing bugs in the old one.  Try
varying the heap size and changing the location of cost-centres, and
see if the problem goes away.

> In both cases I was running with a +RTS -PT -RTS run-time
> option.

Serial time profiles (the -P option) probably don't work, and are of
dubious utility in any case - I'd be interested to know if the problem
goes away if you use -p instead of -P.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: bug report

1998-02-06 Thread Simon Marlow

Simon L Peyton Jones <[EMAIL PROTECTED]> writes:

> > So are types not longer allowed in instance declarations?
> 
> Yes they're allowed, but it's just as if you'd written the 
> expanded type.  Any two instance decls that don't overlap are
> allowed.  You can write
> 
>   instance C (Blah,Int) where ..
>   instance C (Int,Int)  where ..
>   instance C (Blah, Bool) where ...

Isn't it more correct to say that overlapping instances are allowed,
as long as they're never both in scope at the same time?  This might
even be useful, except that it's really hard to control the scope of
instance declarations.

What would be really cool would be if you could write

import Prelude hiding (instance Show (,))
instance Show (Blah,Int) where ..
instance Show (Int,Int)  where ..
instance Show (Blah, Bool) where ...

Cheers,
Simon



> 
> since none of these overlap.  But Show does have an instance for
> (a,b) so you are stuck.  By "overlap" I mean that the instance
> types can be unified.
> 
> Einar says:
> 
> > With the good old 2.something compiler, I could overwrite
> > the default definition of Show for lists and other type constructors, e.g.:
> > 
> > data Blah = Blah deriving (Read,Show)
> > 
> > instance Show [Blah] where
> >   showsPrec d [] r =  r
> >   showsPrec d _ r  = "bla bla ..." ++ r
> > 
> > Duplicate or overlapping instance declarations
> > for `Show [Blah]'
> > at PrelBase.mc_hi and Blah.hs
> 
> Same issue.  Show [a] exists already and overlaps with Show [Blah].
> 
> There is a full discussion of the bad consequences of overlapping
> instance decls in the multi-parameter type class paper
>   http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz
> 
> 3.0 is a bit more restrictive than 2.xx, but it is Righter I think.
> Dissenting opinions welcome.
> 
> Simon
> 
> 
> 

-- 
-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: bug report

1998-02-05 Thread Simon L Peyton Jones


Mark says:

> > 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 types, but that's
> what was so neat about ghc-2.** : they allowed types here.

3.0 is more consistent here.  Suppose I write

show (Blah,3)

should that show as a Tuple or as a (Blah,Int) pair?
What if it was (Show (Blah,3)::Tuple)?  Etc.  

Essentially, resolving overloading is incoherent if you 
allow overlapping instance decls.  

> So are types not longer allowed in instance declarations?

Yes they're allowed, but it's just as if you'd written the 
expanded type.  Any two instance decls that don't overlap are
allowed.  You can write

instance C (Blah,Int) where ..
instance C (Int,Int)  where ..
instance C (Blah, Bool) where ...

since none of these overlap.  But Show does have an instance for
(a,b) so you are stuck.  By "overlap" I mean that the instance
types can be unified.

Einar says:

> With the good old 2.something compiler, I could overwrite
> the default definition of Show for lists and other type constructors, e.g.:
> 
> data Blah = Blah deriving (Read,Show)
> 
> instance Show [Blah] where
>   showsPrec d [] r =  r
>   showsPrec d _ r  = "bla bla ..." ++ r
> 
> Duplicate or overlapping instance declarations
>   for `Show [Blah]'
>   at PrelBase.mc_hi and Blah.hs

Same issue.  Show [a] exists already and overlaps with Show [Blah].

There is a full discussion of the bad consequences of overlapping
instance decls in the multi-parameter type class paper
http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz

3.0 is a bit more restrictive than 2.xx, but it is Righter I think.
Dissenting opinions welcome.

Simon





Re: bug report

1997-12-01 Thread Alex Ferguson


> Did you do 'make install' in ghc, instead of using the binary
> distribution?

I did make install from a build from source, yes, not least as there was
no binary distrib. available  at that point. ;-)

> Hard links are a pain for several reasons - if you install a new ghc
> over the existing one, you have to be sure to remove the old one
> first, or you might stomp on the ghc-2.09 link too...

Having created such links by hand, I can report that the install
script doesn't appear to thusly stomp.  I guess it'd do so if it
changed the file contents, rather than the handle, but don't quote
me on the details of this, as I haven't investigated the details of
what the script does...

Either hard or symbolic is fine by me, mind you.

Cheers,
Alex.



Re: bug report

1997-11-28 Thread Alex Ferguson

> From [EMAIL PROTECTED]  Fri Nov 28 11:48:59 
1997

> This is another file missing from the source distribution.  The new
> one is now up, and it contains all the necessary files.

Can you put this up as a patch, too?

> It does for me - but the sense of the link is reversed (i.e. now ghc
> points to ghc-2.09, which is the real driver).

Odd.  It doesn't seem to do this at all for me.  There's no "ghc-2.09",
and "ghc" isn't a link.  I can't see where in the makefile this should
be happening, either, but as I said, ah dinnae ken GHC makefiles...

>  This is so that you
> can install the new version over the older version.

Why not make it a "hard" link, in the same directory, thereby making
the point of which one is the real one moot?

Cheers,
Alex.



Re: ``bug report''

1998-06-04 Thread Sven Panne

Marc van Dongen wrote:
> [ program omitted ]
> However, for ``f'' the following is reported.
> 
> tmp.lhs:4:
> Pattern match(es) are overlapped in the definition of function `f'
> "=" = ...
> 
> There are no complaints for definition for ``g''.

This is a traditional "bug" GHC, see my question from 27 Jan 98 and
Sigbjorn's reply on 28 Jan 98 in the mailing list archive.

-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



RE: bug report

1998-11-17 Thread Simon Peyton-Jones

Yes, Jeff Lewis demonstrated this bug a while back.
It's fixed in the current sources (4.x) sources.
If it's important then I guess we can retro-fit 3.0x,
but we're planning to put out a (ha!) reliable 4.01 at the
end of Nov.

Thanks for a fine report

Simon


> -Original Message-
> From: Marc van Dongen [mailto:[EMAIL PROTECTED]]
> Sent: Tuesday, November 17, 1998 12:21 PM
> To: [EMAIL PROTECTED]
> Subject: bug report
> 
> 
> 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 p a ss = []
> 
> > instance (Show a,Ord a) => Show (A a) where
> >   showsPrec p a ss = []
> 
> > instance (Show a,Ord a) => Num (A a) where
> >   (+) a a' = a
> 
> > main = return ()
> 
> Main.lhs:18:
> Could not deduce `Show (A a)'
> (arising from an instance declaration at Main.lhs:18)
> from the context (Show a, Ord a)
> Probable cause: missing `Show (A a)' in instance 
> declaration context
> or missing instance declaration for `Show (A a)'
> When checking the superclasses of an instance declaration
> 
> 
> After removing the instance Show (A String) it will compile.
> 
> Am I missing something?
> 
> Regards,
> 
> 
> Marc
> 



Re: bug report

1997-12-01 Thread Simon Marlow

Alex Ferguson <[EMAIL PROTECTED]> writes:

> > Did you do 'make install' in ghc, instead of using the binary
> > distribution?
> 
> I did make install from a build from source, yes, not least as there was
> no binary distrib. available  at that point. ;-)

Right - it's a bug that the link isn't installed from the build tree
when doing 'make install'.  Will fix.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: bug report

1997-11-28 Thread Simon Marlow

Marc van Dongen= <[EMAIL PROTECTED]> writes:

> When compiling with 2.0899,

Gee, I really must fix that...

> I get the following error at linking stage:
> 
> Undefined   first referenced
>  symbol in file
> getBufferMode   /usr/local/ghc-2.09/lib/libHS.a(IOHandle__131.o)
> Main_main_closure   /usr/local/ghc-2.09/lib/libHS.a(GHCmain__7.o)

This is another file missing from the source distribution.  The new
one is now up, and it contains all the necessary files.

Sorry for any inconvenience.

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: bug report

1997-11-29 Thread Simon Marlow

Alex Ferguson <[EMAIL PROTECTED]> writes:

> > It does for me - but the sense of the link is reversed (i.e. now ghc
> > points to ghc-2.09, which is the real driver).
> 
> Odd.  It doesn't seem to do this at all for me.  There's no "ghc-2.09",
> and "ghc" isn't a link.  I can't see where in the makefile this should
> be happening, either, but as I said, ah dinnae ken GHC makefiles...

Did you do 'make install' in ghc, instead of using the binary
distribution?  That might cause the script to be installed as 'ghc'
instead of 'ghc-2.09'.  Will fix for the next release.

> Why not make it a "hard" link, in the same directory, thereby making
> the point of which one is the real one moot?

Hard links are a pain for several reasons - if you install a new ghc
over the existing one, you have to be sure to remove the old one
first, or you might stomp on the ghc-2.09 link too...

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



RE: bug report

2000-03-15 Thread Simon Marlow

> Compiling the following with ghc-4.06 produces an erroneous 
> error message:
> 
> module O where
> 
> a :: Int
> a = 1
> 
> b :: Int
> b = 2
> 
> c :: Int
> c = 3
> 
> f :: Int -> Bool
> f i = case i of
>a -> True
>b -> True
>c -> True
> 
> 
> The compiler complains:
> 
> o.hs:14: Pattern match(es) are overlapped in a group of case 
> alternatives
> beginning
> a:
>   b -> ...
>   c -> ...

You're not an Erlang programmer by any chance are you? :-)

As Kevin pointed out, the warning is correct.  In Haskell, a variable name
in a pattern is always a new binding, and shadows any existing bindings of
the same name.

Cheers,
Simon



RE: Bug report

2000-10-06 Thread Simon Peyton-Jones

Axel

Quite right; thank you for reporting it.  The fix was trivial, but 
we're not planning 4.08.2 for a while (if ever).  So a workaround is to
write
import PrelIOBase
foo = returnIO

in your module. Or have at least one 'foreign export dynamic' in your
module.

Simon

| -Original Message-
| From: Axel Krauth [mailto:[EMAIL PROTECTED]]
| Sent: 05 October 2000 16:19
| To: [EMAIL PROTECTED]
| Subject: Bug report
| 
| 
| -- Sorry, but if ghc tells me to report it..
| --
| -- Using :The Glorious Glasgow Haskell Compilation System, 
| version 4.08.1
| -- (if this is also needed) : gcc 2.95.2 ( also egcs 1.1.2)
| -- ghc -v -fglasgow-exts -i/usr/local/lib/ghc-4.08.1/imports/lang/  \
| -- -o bug bug.hs -lHSlang 
| --
| -- message by ghc (ghc -v in attachment) : 
| --  panic! (the `impossible' happened):
| --tcLookupGlobalValue: .PrelIOBase.returnIO{-0B,s-}
| --Please report it as a compiler bug to 
| [EMAIL PROTECTED]
| 
| module Main where
| 
| import Foreign
| 
| foreign export ccall "gccd" mygcd :: Int -> Int -> Int 
| main =
| do
| putStrLn "No bug"
| 
| mygcd  a b = if (a==b) then a 
|   else if (ahttp://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: bug report

2003-01-22 Thread Simon Marlow
> I am reporting a bug in the GHCi Haskell interpreter as requested by 
> the program itself. GHC is 5.04.2 running on SunOS 5.8.
> 
> The interpreter encountered a panic condition when trying to load a
> parser produced by Happy the parser generator.

Yes, this is a known bug in 5.04.2 (although I don't think it was
reported on the lists, so you can be forgiven for not having seen it!).
The workaround is to avoid using the 'a' and 'g' flags to Happy, or to
compile the parser using GHC before loading it into GHCi.

The bug was fixed in the HEAD, but was deemed to difficult to fix in the
5.04.x branch too.

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



RE: Bug report.

2004-04-19 Thread Simon Marlow
On 25 March 2004 09:06, MR K P SCHUPKE wrote:

> Started getting:
> 
> ghc-6.2.1.20040313: panic! (the `impossible' happened, GHC version
> 6.2.1.20040313): mkTyVar a1 {- tv a75q -}
> 
> Please report it as a compiler bug to
> [EMAIL PROTECTED], 
> or http://sourceforge.net/projects/ghc/.
> 
> today... definitely a but to do with class inference, as it started
> appearing aftyer changing some instance constraints and fundeps on
> classes. 
> 
> Can't really be a lot more specific as code is big. Let me know if
> you want 
> me to produce a small code extract which triggers it.

I'm not sure if anyone followed up on this... if you're still having the
problem, could you send us some code to reproduce?

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


RE: bug report

2006-01-04 Thread Simon Peyton-Jones
Hi Alex

Yes I remember talking to you.  It'd be interesting to see your web
crawler when you are done.

Meanwhile, you've definitely hit a bug.  Can you make a reproducible
test case so we can look into it?

Simon

| -Original Message-
| From: Alessandro Warth [mailto:[EMAIL PROTECTED]
| Sent: 29 December 2005 20:26
| To: glasgow-haskell-bugs@haskell.org
| Cc: Simon Peyton-Jones
| Subject: bug report
| 
| Hello,
| 
| My name is Alex Warth. I've been working on a multi-threaded web
| crawler that uses STM, and I just got a strange error message while
| running my program:
| 
| a.out: internal error: scavenge_stack: weird activation record found
on stack: 6
| Please report this as a bug to glasgow-haskell-bugs@haskell.org,
| or http://www.sourceforge.net/projects/ghc/
| 
| I'm not sure whether or not it makes a difference, but I got the error
| message above directly after the following error message:
| 
| a.out: getHostByName: does not exist (no such host entry)
| 
| I've been able to determine that this is not a sporadic error. In
| fact, this happens every time I get a "getHostByName: does not exist
| (no such host entry)" error message. I can make this happen whenever I
| want.
| 
| Please let me know if there's any other information you would like me
| to send you. Maybe the source code would be helpful?
| 
| Thanks,
| Alex Warth
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report

2006-05-10 Thread Duncan Coutts
On Tue, 2006-05-02 at 08:56 -0700, Steve Dekorte wrote:
> % darcs annotate slice
> darcs: internal error: evacuate: strange closure type 14402
>  Please report this as a bug to glasgow-haskell-bugs@haskell.org,
>  or http://www.sourceforge.net/projects/ghc/

Would you mind answering a few more questions so that we have a chance
to track down this bug:

  * Could you tell us what version of darcs that was?
  * What OS were you using? (eg Debian, Fedora, OS X, etc)
  * what kind of computer? (eg x86, x86_64)
  * Did you compile darcs yourself? if so version of GHC did you
use?
  * Did you get darcs from a pre-compiled package? If so which one?
  * When you did "annotate slice" were you working with a very large
repository or a small one?
  * Was the bug reproducible? Did it happen just the once or every
time you ran that command?

Thanks.

Duncan

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report

2006-05-10 Thread Steve Dekorte


On 10 May 2006, at 02:17 am, Duncan Coutts wrote:

On Tue, 2006-05-02 at 08:56 -0700, Steve Dekorte wrote:

% darcs annotate slice
darcs: internal error: evacuate: strange closure type 14402
 Please report this as a bug to glasgow-haskell-bugs@haskell.org,
 or http://www.sourceforge.net/projects/ghc/


Would you mind answering a few more questions so that we have a chance
to track down this bug:

  * Could you tell us what version of darcs that was?


1.0.5rc2 (release candidate )


  * What OS were you using? (eg Debian, Fedora, OS X, etc)


OSX 10.3.9


  * what kind of computer? (eg x86, x86_64)


G5 PPC


  * Did you compile darcs yourself? if so version of GHC did you
use?


I don't recall.


  * Did you get darcs from a pre-compiled package? If so which one?
  * When you did "annotate slice" were you working with a very 
large

repository or a small one?


large


  * Was the bug reproducible? Did it happen just the once or every
time you ran that command?


yes

-- Steve

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report

2006-05-10 Thread Gregory Wright


Steve,

If this compiler were ghc 6.4.2, this is probably bug 751, which
has been reported by by others using ghc 6.4.2 from darwinports
while building darcs.

I am building a compiler with debugging turned on; perhaps
that will give some clues about the apparent RTS crash that we've
been seeing.

-Greg


On May 10, 2006, at 3:52 PM, Steve Dekorte wrote:



On 10 May 2006, at 02:17 am, Duncan Coutts wrote:

On Tue, 2006-05-02 at 08:56 -0700, Steve Dekorte wrote:

% darcs annotate slice
darcs: internal error: evacuate: strange closure type 14402
 Please report this as a bug to glasgow-haskell- 
[EMAIL PROTECTED],

 or http://www.sourceforge.net/projects/ghc/


Would you mind answering a few more questions so that we have a  
chance

to track down this bug:

  * Could you tell us what version of darcs that was?


1.0.5rc2 (release candidate )


  * What OS were you using? (eg Debian, Fedora, OS X, etc)


OSX 10.3.9


  * what kind of computer? (eg x86, x86_64)


G5 PPC


  * Did you compile darcs yourself? if so version of GHC did you
use?


I don't recall.

  * Did you get darcs from a pre-compiled package? If so which  
one?
  * When you did "annotate slice" were you working with a very  
large

repository or a small one?


large

  * Was the bug reproducible? Did it happen just the once or  
every

time you ran that command?


yes

-- Steve

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report

2006-05-18 Thread Simon Marlow

Steve Dekorte wrote:


On 10 May 2006, at 02:17 am, Duncan Coutts wrote:


On Tue, 2006-05-02 at 08:56 -0700, Steve Dekorte wrote:


% darcs annotate slice
darcs: internal error: evacuate: strange closure type 14402
 Please report this as a bug to glasgow-haskell-bugs@haskell.org,
 or http://www.sourceforge.net/projects/ghc/



Would you mind answering a few more questions so that we have a chance
to track down this bug:

  * Could you tell us what version of darcs that was?


1.0.5rc2 (release candidate )


  * What OS were you using? (eg Debian, Fedora, OS X, etc)


OSX 10.3.9


  * what kind of computer? (eg x86, x86_64)


G5 PPC


  * Did you compile darcs yourself? if so version of GHC did you
use?


I don't recall.


In order to track down the bug, we need to know which version of GHC you 
used.  Could you compile darcs again and test whether the bug still 
occurs?  Note that if you are using 6.4.2, GHC has a known bug on MacOS 
X that could cause the symptom you saw.


Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report 3.00

1998-02-06 Thread Sigbjorn Finne


Marc van Dongen= writes:
> 
> While compiling some happy output with 3.00 I came
> across the following:
> 
> 
> NOTE: Simplifier still going after 4 iterations; bailing out.
> 
> NOTE: Simplifier still going after 4 iterations; bailing out.
> 
> panic! (the `impossible' happened):
> fun_result_ty: 6 GHC.Int#{-3e-}
>  -> GHC.Int#{-3e-}
>  -> b_trKC
>  -> PolyParse.HappyState{-rq9-} b_trKC c_trKD
>  -> [PolyParse.HappyState{-rq9-} b_trKC c_trKD]
>  -> c_trKD
> 

Thanks for the report, this looks suspiciously similar to the panic
reported by Sven a couple of days ago (I attach Simon's reply to it.)

Bottom line: try compiling the module with -fno-update-analysis and
see if that side steps it.

--Sigbjorn

Simon L Peyton Jones writes:
> > One can play funny games with GHC-3.00 and the following program
> > (a small fragment of a Happy-generated parser):
> > 
> > --
> > module Foo ( happyParse ) where
> > 
> > action_0 1 = \j tk _ -> action_1 j j tk (HappyState action_1)
> > 
> > action_1 3 = error "Bar"
> > action_1 _ = \i tk st@(HappyState action) sts stk -> action (-1) (-1) tk st sts 
>(Just i : stk)
> > 
> > happyParse = action_0 2 2 '-' (HappyState action_0) [] [] 2
> > 
> > newtype HappyState b c =
> >HappyState (Int -> Int -> b -> HappyState b c -> [HappyState b c] -> c)
> > --
> 
> Great program!  Thanks for isolating it.
> 
>   Simon: pls add to regression suite
> 
> There are two problems.  One is a long-standing bit of grubbiness
> in the code generator; hence fun_result_ty panic.  I've fixed that
> (still grubbily, I fear).
> 
> GHC goes into a loop in the update analyser.  Reason: the 
> recursive contravariance of HappyState.  Consider:
> 
>   action_1 j j tk (HappyState action_1) sts stk
> = {unfold action_1}
>   action_1 (-1) (-1) tk (HappyState action_1) sts (Just j:stk)
> = {unfold action_1 again}
>   ... 
> 
> Neither action_0 nor action_1 is recursive, but infinite unfolding
> can still occur.  This can cause the simplifier to loop, though
> on this occasion it doesn't, but only because action_1 is
> considered too big to unfold.  But it does make the update analyser
> loop, for some obscure reason.  It wouldn't surprise me if the
> strictness analyser looped too, but it doesn't.
> 
> For some reason there's no flag to switch off the update analyser.
> It does very little good anyway, so just switch it off by force
> in ghc/driver/ghc.lprl (look for -fupdate-anal).
> 
> I've known about the possibility of looping in the simpifier for some time, but
> never seen it in a real program.  I have no idea how to spot it in a clean way,
> and without disabling lots of useful inlining.  (I prevent looping mainly by
> treating letrec carefully.)  Ideas welcome
> 
> Simon
> 



Re: bug report 3.00

1998-02-06 Thread Simon L Peyton Jones


> > panic! (the `impossible' happened):
> > fun_result_ty: 6 GHC.Int#{-3e-}
> >  -> GHC.Int#{-3e-}
> >  -> b_trKC
> >  -> PolyParse.HappyState{-rq9-} b_trKC c_trKD
> >  -> [PolyParse.HappyState{-rq9-} b_trKC c_trKD]
> >  -> c_trKD
> > 
> 
> Thanks for the report, this looks suspiciously similar to the panic
> reported by Sven a couple of days ago (I attach Simon's reply to it.)
> 
> Bottom line: try compiling the module with -fno-update-analysis and
> see if that side steps it.

Not so.  It was this problem:

> > There are two problems.  One is a long-standing bit of grubbiness
> > in the code generator; hence fun_result_ty panic.  I've fixed that
> > (still grubbily, I fear).


I didn't produce a patch because I fixed it by modifying a number
of files in a tidy-up effort.   Yell if this is a show-stopper for you
and we'll accelerate a fixed 3.0

S




RE: bug report 4.00

1998-11-17 Thread Simon Marlow

> 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/includes
>  /usr/local/include
>  /usr/local/sparc-sun-solaris2.5/include
>  /usr/local/lib/gcc-lib/sparc-sun-solaris2.5/2.7.2/include
>  /usr/include
> End of search list.
> /usr/local/ghc-4.00/lib/ghc-4.00/includes/ClosureMacros.h:140:
>  unterminated character constant
> /usr/local/ghc-4.00/lib/ghc-4.00/includes/StgMacros.h:87: 
> unterminated string or character constant
> 
> real0.3
> user0.2
> sys 0.0
> deleting... /tmp/ghc6070.cpp /tmp/ghc6070.hi /tmp/ghc6070.hc 
> /tmp/ghc6070_stb.c /tmp/ghc6070_stb.h ghc6070.c ghc6070.s 
> /tmp/ghc6070_o.s
> 
> rm -f /tmp/ghc6070*
> make: *** [Result.o] Error 1

Are you passing any extra flags to GHC?  Could you send a copy of the file
and a full transcript of the compilation with '-v' please.

Cheers,
Simon

-- 
Simon Marlow 
Microsoft Research Ltd., Cambridge, U.K.
 



RE: Bug Report: stg_ap_p_ret

2004-12-08 Thread Simon Marlow
I think you forgot to attach the code!  BTW, we need the source to the
whole program, and instructions for reproducing the problem.  If the
program uses pseudo randomness, then have it output the seed at the
beginning of the run so that we can run it again with the same seed.

Cheers,
Simon

On 07 December 2004 15:37, oriel maxime wrote:

> Good day.  I'm using GHC 6.2.1, and have had much
> success with it.  However, yesterday I got a strange
> error I've never before seen.
> 
> Mosaic: internal error: stg_ap_p_ret
> Please report this as a bug to glasgow-haskell-
> [EMAIL PROTECTED], or
> http://www.sourceforge.net/projects/ghc/
> 
> I'm running Windows XP Service Pack 1.
> 
> The only obvious thing from the run is that several
> generation 1 garbage collections resulted in a
> substantially smaller allocation than before (99% of
> all space was free over these two collections) and
> something "bad" happened.
> 
> I've included the console data (trace output, the
> -Sstderr output, the parameters used to run the
> program, the OS version at the top...), as well as the
> code for the main module, the .hi file, and the .o
> file (in case these help).
> 
> Neither the main module nor any of its included
> modules use FFI in any capacity.  Use of unsafe IO is
> limited to caching and tracing.
> 
> Note:  the reference to "threads" solved, killed, etc.
> are to an abstraction of a "DeductiveThread" for a
> backtracking algorithm, which is the core logic of
> this program.  No modules in this program use
> Control.Concurrent in any capacity.
> 
> I'd be happy to provide additional details, additional
> source, etc.  I'm going to rerun the program and see
> if the problem reoccurs:  the program does use
> randomness, so it's possible that the problem won't
> appear again.
> 
> The easiest way to contact me is at this email
> address.  I check it regularly during the week, and
> periodically over the weekend.  Please don't hesitate
> to ask if you have any questions, or if there's some
> other way I can help.  I've quite enjoyed the GHC
> product, have written some significantly non-trivial
> programs using it, and would be happy to assist in
> making it a better and more robust tool.
> 
> Thanks, and I look forward to hearing from you...
> 
> oriel
> 
> 
> 
> __
> Do you Yahoo!?
> The all-new My Yahoo! - Get yours free!
> http://my.yahoo.com
> 
> 
> ___
> Glasgow-haskell-bugs mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

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


RE: bug report, stg_ap_v_ret

2005-10-28 Thread Simon Marlow
On 27 October 2005 21:40, Tim Daly Jr. wrote:

> [EMAIL PROTECTED]:~$ darcs get /e/phpoo
> Copying patch 1066 of 2079...darcs.exe: internal error: stg_ap_v_ret
> Please report this as a bug to glasgow-haskell-bugs@haskell.org,
> or http://www.sourceforge.net/projects/ghc/
> [EMAIL PROTECTED]:~$ darcs --version
> 1.0.3 (release)
> 
> Let me know if there's anything else I can do to help.

Similar errors have been reported before... basically we need a
reproducible test case in order to track it down.  If it happens
reliably for you with that repository (or even semi-reliably), then can
you just tar up the darcs repo and send it to us?  

Also we need to know the provenance of your darcs binary, i.e. which
version of GHC was used to compile it and on which platform.

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: bug report, stg_ap_v_ret

2005-10-28 Thread Tim Daly Jr.
On Fri, 2005-10-28 at 09:54 +0100, Simon Marlow wrote:
> Similar errors have been reported before... basically we need a
> reproducible test case in order to track it down.  If it happens
> reliably for you with that repository (or even semi-reliably), then can
> you just tar up the darcs repo and send it to us?  

I can reproduce it reliably.  Unfortunately, I can't send you the
repository.

> Also we need to know the provenance of your darcs binary, i.e. which
> version of GHC was used to compile it and on which platform.

The darcs binary I used is available here:
.  I was working on a
win2k system using mingw tools.  The problem doesn't show up when using
this version:
.

--
-Tim


___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: bug report: picoseconds handling in System.Time

2007-08-20 Thread Simon Marlow

Andrei Paskevich wrote:
The diffClockTimes function can generate TimeDiff's with 
a negative value of tdPicosec. When you pass such a TimeDiff 
to addToClockTime, the latter may send negative picoseconds 
to toClockTime, provoking the error "picoseconds out of range".


While we are at it, please, teach normalizeTimeDiff to normalize
tdPicoSeconds, too. This misfeature hangs around for too long :)

Best regards,
Andrei

P.S. I'm not subscribed to the list, so please cc: me if needed.


There are a number of serious problems with System.Time.  If you're doing 
calculations involving time periods, I strongly suggest moving to the new 
time package (Data.Time etc.).


Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Bug Report: Export List in Module

2000-01-24 Thread Simon Marlow


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

Yes, GHC's parser is a little more liberal about extra punctuation than it
should be.  I don't particularly want to fix this, but if everyone gangs up
and beats me about the head with copies of the Haskell 98 Report then I
might concede.

Cheers,
Simon



RE: Bug report for ghci: using Word64

2002-01-07 Thread Julian Seward (Intl Vendor)


We never really implemented full 64-bit support in the interpreter.
We had a scheme for doing that, and some infrastructure was put in
post 5.02.1, but connecting it all up for 5.02.2 (released today?)
was considered too disruptive for a patchlevel release, so I guess
it will only see the light of day when it is made to work in the
head (current development branch).  + to tell the truth I think
we just forgot all about it.  Oops!

The interpreter (ghci) will have problems if you ask it to compile
code which 

* deals directly with unboxed 64 bit ints   (Int64#)
* passes them between compiled and interpreted code

Note (perhaps critically) that boxed 64-bit Ints (Int64)
are harmless, provided that the bytecode generator never
has to see them unboxedly.  So you may be able to workaround
by cramming all your low-level 64-bit stuff into a single
module or group thereof, which you compile with ghc,
and then load into ghci, with the rest of your modules 
interpreted.  This will only work if the compiled modules
don't have Int64# in the signatures of any exported fns,
*and* no unfoldings which might surreptitiously expose
Int64#s are exported either.  Ensuring the latter is 
difficult at best.

J


| -Original Message-
| From: Laura McKinney [mailto:[EMAIL PROTECTED]] 
| Sent: Monday, January 07, 2002 4:47 PM
| To: [EMAIL PROTECTED]
| Subject: Bug report for ghci: using Word64
| 
| 
| We are using Word64 and encountered the following problem 
| upon loading into 
| ghci:
| 
| ghc-5.02.1: panic! (the `impossible' happened, GHC version 5.02.1):
|   ByteCodeGen.mkUnpackCode LW_
| 
| Program works under ghc.
| 
| Laura McKinney
| 
| ___
| Glasgow-haskell-bugs mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
| 

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



Re: [bug report] labeled fields in ghc-2.03

1997-05-20 Thread Simon L Peyton Jones


Thanks for the bug report.  What you say is all too true.  It's fixed
in my working copy; pending the next release I guess you'll just have to
work around it.  Sorry.

Simon

| From: Tomasz Cholewo <[EMAIL PROTECTED]>
| Date: Tue, 20 May 1997 05:10:04 GMT
| Hi,
| 
| ghc-2.03 cannot compile the following code, which I think is correct
| according to the Report:
| 
| > data X = A {a :: Int} | B {a :: Int}
| 
| The error message is: 
| 
| Conflicting definitions for:  a
|   Defined at bug4.lhs:2
|   Defined at bug4.lhs:2
| 
| In addition the following snippet
| 
| > data X = A {a :: Int}
| > y = let A {a} = x
| > in a
| 
| fails with:
| bug4.lhs:4:5: Not a valid LHS on input: "in"
| 
| Rewriting it as an explicit 
| 
| > y = case x of
| >   A {a} -> a
| 
| seems to help.
|   
| I guess that the support for labeled fields is not quite implemented
| yet?  In Hugs the above two examples are working.
| 
| -- Tomasz Cholewo



Re: [bug report] ghc-2.03 on mips-sgi-irix6

1997-05-13 Thread Sigbjorn Finne



Tomasz Cholewo writes:
> Hello,
> 
> Running ghc on the attached (admittedly ugly) file bug2.lhs yields:
> -
> Warning: discarding polymorphic case:tpl_s4Ez
> Warning: discarding polymorphic case:tpl_s4F5
> Warning: discarding polymorphic case:tpl_s4Fd
> Warning: discarding polymorphic case:tpl_s4Fl
> Warning: discarding polymorphic case:tpl_s4Ft
> 
> panic! (the `impossible' happened):
>   lookupBindC:no info!
> for: d.Eval_aY2
> (probably: data dependencies broken by an optimisation pass)
>

Hi,

thanks for the bug report - a real fix in the next release (i.e.,
support for polymorphic strictness annotations). If you haven't
done so already, I suggest you sidestep the 2.03 panic by dropping the
use of ! on polymorphic fields.

--Sigbjorn



Re: [bug report] ghc-2.03: wrong (!!) fixity; instances for `newtype'

1997-05-21 Thread Simon L Peyton Jones


Tomasz,

Thanks for the fine bug reports. Keep em coming.

| Source of the problem is a declaration in PrelBase.lhs:
|   infixr 9  !!
| According to the Report it should read:
|   infixl 9  !!

Fixed.

| 2. The following code
| 
| > newtype Age = MkAge Int deriving (Eq, Show)
| > instance Num (Age)

Your code is fine, it's GHC that's at fault. You are rightly pushing on
newtypes which aren't very throughly tested.  

I'll fix this asap.  We're planning a source release within a fortnight,
which will contain the fixes.

Simon



Re: [bug report] ghc-2.03: exponential number of error messages

1997-05-22 Thread Simon L Peyton Jones



| Each additional, no matter how trivial definition causes that the
| compiler starts to produces twice as many error messages. In general
| adding n definitions gives raise to 7 * 2^n errors, e.g., adding:

Yes, I tripped over this too!  It could only happen in a compiler written in
a functional language.  The typechecker error recovery was doing a sort of
backtracking thing.

Simon