[GHC] #2277: GHCi silently aborts on 'take' computation

2008-05-09 Thread GHC
#2277: GHCi silently aborts on 'take' computation
---+
Reporter:  cdsmith |   Owner:
Type:  bug |  Status:  new   
Priority:  normal  |   Component:  GHCi  
 Version:  6.9 |Severity:  normal
Keywords:  |Testcase:
Architecture:  x86_64 (amd64)  |  Os:  Linux 
---+
 With latest GHC from darcs repository, on an AMD64 system, performing a
 'take' computation with an infinite or very long list causes GHCi to exit
 without warning.  This happens regardless of whether the list is the
 result of {{{let x = 2:x}}} or {{{let x = [2,2..]}}} or {{{let x =
 replicate 1 2}}}.

 There is no problem in GHC 6.8.2.

 {{{
 [EMAIL PROTECTED]:~$ ghci -v
 GHCi, version 6.9.20080507: http://www.haskell.org/ghc/  :? for help
 Glasgow Haskell Compiler, Version 6.9.20080507, for Haskell 98, stage 2
 booted by GHC version 6.8.2
 Using package config file: /usr/local/lib/ghc-6.9.20080507/package.conf
 hiding package bytestring-0.9 to avoid conflict with later version
 bytestring-0.9.1.0
 wired-in package ghc-prim mapped to ghc-prim-0.1
 wired-in package integer mapped to integer-0.1
 wired-in package base mapped to base-3.0
 wired-in package rts mapped to rts-1.0
 wired-in package haskell98 mapped to haskell98-1.0.1
 wired-in package template-haskell mapped to template-haskell-2.2
 wired-in package ndp not found.
 Hsc static flags: -static
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 hiding package bytestring-0.9 to avoid conflict with later version
 bytestring-0.9.1.0
 wired-in package ghc-prim mapped to ghc-prim-0.1
 wired-in package integer mapped to integer-0.1
 wired-in package base mapped to base-3.0
 wired-in package rts mapped to rts-1.0
 wired-in package haskell98 mapped to haskell98-1.0.1
 wired-in package template-haskell mapped to template-haskell-2.2
 wired-in package ndp not found.
 hiding package bytestring-0.9 to avoid conflict with later version
 bytestring-0.9.1.0
 wired-in package ghc-prim mapped to ghc-prim-0.1
 wired-in package integer mapped to integer-0.1
 wired-in package base mapped to base-3.0
 wired-in package rts mapped to rts-1.0
 wired-in package haskell98 mapped to haskell98-1.0.1
 wired-in package template-haskell mapped to template-haskell-2.2
 wired-in package ndp not found.
 hiding package bytestring-0.9 to avoid conflict with later version
 bytestring-0.9.1.0
 wired-in package ghc-prim mapped to ghc-prim-0.1
 wired-in package integer mapped to integer-0.1
 wired-in package base mapped to base-3.0
 wired-in package rts mapped to rts-1.0
 wired-in package haskell98 mapped to haskell98-1.0.1
 wired-in package template-haskell mapped to template-haskell-2.2
 wired-in package ndp not found.
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Prelude> let x = 2:x
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Prelude> take 1000 x
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 
[2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2
 
,2,2,

[GHC] #2276: foreign import stdcall "&foo" doesn't work

2008-05-09 Thread GHC
#2276: foreign import stdcall "&foo" doesn't work
-+--
Reporter:  simonmar  |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  _|_
   Component:  Compiler  | Version:  6.8.2  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  x86   |  Os:  Windows
-+--
 Importing a label with the stdcall calling convention fails to remember
 the stdcall attribute and add the appropriate '@n' suffix to the label on
 Windows.  e.g.

 {{{
 foreign import stdcall "&foo" foo :: FunPtr (CInt -> IO ())
 }}}

 should result in a reference to "[EMAIL PROTECTED]", but doesn't.  This breaks 
the
 Win32 library, which does something like this for `genericWndProc` in
 `Graphics/Win32/Window.hsc`.

 Somewhat related to to #1288 .

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1958: collect2: ld terminated with signal 10 [Bus error]: Building parsec on a PPC Mac OS X 10.5 Leopard as part of GHC 6.9

2008-05-09 Thread GHC
#1958: collect2: ld terminated with signal 10 [Bus error]: Building parsec on a
PPC Mac OS X 10.5 Leopard as part of GHC 6.9
-+--
 Reporter:  thorkilnaur  |  Owner:  thorkilnaur
 Type:  bug  | Status:  new
 Priority:  high |  Milestone:  Not GHC
Component:  Compiler |Version:  6.8.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  powerpc
   Os:  MacOS X  |  
-+--
Comment (by eelco):

 It took me a bit longer than expected, but I can confirm that ghc 6.8.2
 built succesfully using XCode 3.1 (from the iPhone SDK package).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2269: Word type to Double or Float conversions are slower than Int conversions

2008-05-09 Thread GHC
#2269: Word type to Double or Float conversions are slower than Int conversions
+---
 Reporter:  dons|  Owner:  [EMAIL PROTECTED]
 Type:  feature request | Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Compiler|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  rules, performance, double  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by igloo):

  * difficulty:  => Unknown
  * milestone:  => 6.10 branch

Comment:

 I'd like `word2Double#` and `word2Float#` for integer-simple too, so it
 sounds good to me!

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2275: Poor indication of type error location

2008-05-09 Thread GHC
#2275: Poor indication of type error location
-+--
 Reporter:  guest|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone: 
Component:  Compiler (Type checker)  |Version:  6.8.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by igloo):

  * difficulty:  => Unknown

Old description:

> Using {-# OPTIONS_GHC -XArrows -fno-monomorphism-restriction #-}, and
> Yampa
> Starting from line 32, my program contains:
>
> fireworkSF :: Point2 GL.GLdouble -> Point2 GL.GLdouble -> Object
> fireworkSF p0 pFinal = proc _ -> do
>   rec
> position <- (p0 .+^) ^<< integral -< v0
> let shouldExplode = position == pFinal
> let killReq = if shouldExplode then Event () else noEvent
> let spawnReq = if shouldExplode
>  then Event (Explode pFinal)
>  else noEvent
>   returnA -< ObjectOutput {oState = FireworkState position
>   ,oKillReq = killReq
>   ,oSpawnReq = spawnReq}
>   where
> v0 = (pFinal ^-^ p0) ^/ 2
>
> The type error reports:
> Firework.hs:32:0:
> Couldn't match expected type `Point2 GL.GLdouble'
>against inferred type `Vector2 GL.GLdouble'
> When using functional dependencies to combine
>   AffineSpace (Point2 a) (Vector2 a) a,
> arising from the instance declaration at 
>   AffineSpace (Point2 GL.GLdouble) (Point2 GL.GLdouble) a,
> arising from a use of `.+^' at Firework.hs:34:16-23
> When generalising the type(s) for `fireworkSF'
>
> Indicating that the bug is something to do with line 34.  The actual bug
> is that the last line of the paste should read:
> v0 = (pFinal .-. p0) ^/ 2

New description:

 Using {-# OPTIONS_GHC -XArrows -fno-monomorphism-restriction #-}, and
 Yampa
 Starting from line 32, my program contains:
 {{{
 fireworkSF :: Point2 GL.GLdouble -> Point2 GL.GLdouble -> Object
 fireworkSF p0 pFinal = proc _ -> do
   rec
 position <- (p0 .+^) ^<< integral -< v0
 let shouldExplode = position == pFinal
 let killReq = if shouldExplode then Event () else noEvent
 let spawnReq = if shouldExplode
  then Event (Explode pFinal)
  else noEvent
   returnA -< ObjectOutput {oState = FireworkState position
   ,oKillReq = killReq
   ,oSpawnReq = spawnReq}
   where
 v0 = (pFinal ^-^ p0) ^/ 2
 }}}
 The type error reports:
 {{{
 Firework.hs:32:0:
 Couldn't match expected type `Point2 GL.GLdouble'
against inferred type `Vector2 GL.GLdouble'
 When using functional dependencies to combine
   AffineSpace (Point2 a) (Vector2 a) a,
 arising from the instance declaration at 
   AffineSpace (Point2 GL.GLdouble) (Point2 GL.GLdouble) a,
 arising from a use of `.+^' at Firework.hs:34:16-23
 When generalising the type(s) for `fireworkSF'
 }}}
 Indicating that the bug is something to do with line 34.  The actual bug
 is that the last line of the paste should read:
 {{{
 v0 = (pFinal .-. p0) ^/ 2
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2275: Poor indication of type error location

2008-05-09 Thread GHC
#2275: Poor indication of type error location
+---
Reporter:  guest|Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Compiler (Type checker)  |  Version:  6.8.2  
Severity:  normal   |   Resolution: 
Keywords:   | Testcase: 
Architecture:  Unknown  |   Os:  Unknown
+---
Comment (by guest):

 Sorry, here's the code again:
 {{{

 fireworkSF :: Point2 GL.GLdouble -> Point2 GL.GLdouble -> Object
 fireworkSF p0 pFinal = proc _ -> do
   rec
 position <- (p0 .+^) ^<< integral -< v0
 let shouldExplode = position == pFinal
 let killReq = if shouldExplode then Event () else noEvent
 let spawnReq = if shouldExplode
  then Event (Explode pFinal)
  else noEvent
   returnA -< ObjectOutput {oState = FireworkState position
   ,oKillReq = killReq
   ,oSpawnReq = spawnReq}
   where
 v0 = (pFinal ^-^ p0) ^/ 2
 }}}

 And the error:
 {{{
 Firework.hs:32:0:
 Couldn't match expected type `Point2 GL.GLdouble'
against inferred type `Vector2 GL.GLdouble'
 When using functional dependencies to combine
   AffineSpace (Point2 a) (Vector2 a) a,
 arising from the instance declaration at 
   AffineSpace (Point2 GL.GLdouble) (Point2 GL.GLdouble) a,
 arising from a use of `.+^' at Firework.hs:34:16-23
 When generalising the type(s) for `fireworkSF'
 }}}

 and the correct line:
 {{{ v0 = (pFinal .-. p0) ^/ }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2275: Poor indication of type error location

2008-05-09 Thread GHC
#2275: Poor indication of type error location
+---
Reporter:  guest|   Owner: 
Type:  bug  |  Status:  new
Priority:  normal   |   Component:  Compiler (Type checker)
 Version:  6.8.2|Severity:  normal 
Keywords:   |Testcase: 
Architecture:  Unknown  |  Os:  Unknown
+---
 Using {-# OPTIONS_GHC -XArrows -fno-monomorphism-restriction #-}, and
 Yampa
 Starting from line 32, my program contains:

 fireworkSF :: Point2 GL.GLdouble -> Point2 GL.GLdouble -> Object
 fireworkSF p0 pFinal = proc _ -> do
   rec
 position <- (p0 .+^) ^<< integral -< v0
 let shouldExplode = position == pFinal
 let killReq = if shouldExplode then Event () else noEvent
 let spawnReq = if shouldExplode
  then Event (Explode pFinal)
  else noEvent
   returnA -< ObjectOutput {oState = FireworkState position
   ,oKillReq = killReq
   ,oSpawnReq = spawnReq}
   where
 v0 = (pFinal ^-^ p0) ^/ 2

 The type error reports:
 Firework.hs:32:0:
 Couldn't match expected type `Point2 GL.GLdouble'
against inferred type `Vector2 GL.GLdouble'
 When using functional dependencies to combine
   AffineSpace (Point2 a) (Vector2 a) a,
 arising from the instance declaration at 
   AffineSpace (Point2 GL.GLdouble) (Point2 GL.GLdouble) a,
 arising from a use of `.+^' at Firework.hs:34:16-23
 When generalising the type(s) for `fireworkSF'

 Indicating that the bug is something to do with line 34.  The actual bug
 is that the last line of the paste should read:
 v0 = (pFinal .-. p0) ^/ 2

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs