Fwd: GHC Bug report

2009-10-01 Thread Jason Dagit
[I just found out that there is a dedicated bugs email address so forwarding
the original message there.]

Hello,

I've created a small example of the program I have at this URL with the
output of -ddump-simpl:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=10109#a10109

Notice that on line 139, I would like it if the Word8 could be passed
without boxing.
The full program text is here also in case the link above disappears:
\begin{code}
{-# LANGUAGE BangPatterns, MagicHash #-}
module Main where
import GHC.Word ( Word8(W8#) )
import GHC.Exts ( Int#, Int(I#), Ptr(..), Word#, Word(W#) )
import GHC.Prim ( indexWord8OffAddr#, (==#), (=#), (+#), word2Int#, Addr# )

isSpaceWord8 :: Word8 - Bool
isSpaceWord8 !w =
w == 0x20 ||-- ' '
w == 0x09 ||-- '\t'
w == 0x0A ||-- '\n'
w == 0x0D   -- '\r'
{-# INLINE isSpaceWord8 #-}

firstnonspace :: Ptr Word8 - Int - Int - Int
firstnonspace (Ptr p) (I# n) (I# m) = I# (first p n m)
  where
  first :: Addr# - Int# - Int# - Int#
  first addr n' m'
  | n' =# m' = n'
  | otherwise = if (not (isSpaceWord8 ch))
  then n'
  else first addr (n' +# 1#) m'
where
ch = W8# (indexWord8OffAddr# addr n')
{-# INLINE firstnonspace #-}

main = return ()
\end{code}

The output from ghc -O2 -ddump-simpl is:
\begin{core}

 Tidy Core 
Main.a :: GHC.Prim.State# GHC.Prim.RealWorld
  - (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
[GlobalId]
[Arity 1
 NoCafRefs
 Str: DmdType L]
Main.a =
  \ (s_aHK :: GHC.Prim.State# GHC.Prim.RealWorld) -
(# s_aHK, GHC.Unit.() #)

Main.a1 :: GHC.Prim.State# GHC.Prim.RealWorld
   - (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
[GlobalId]
[Arity 1
 Str: DmdType L]
Main.a1 =
  GHC.TopHandler.a5
@ ()
(Main.a
 `cast` (sym ((GHC.IOBase.:CoIO) ())
 :: GHC.Prim.State# GHC.Prim.RealWorld
- (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
  ~
GHC.IOBase.IO ()))

Main.main :: GHC.IOBase.IO ()
[GlobalId]
[Arity 1
 NoCafRefs
 Str: DmdType L]
Main.main =
  Main.a
  `cast` (sym ((GHC.IOBase.:CoIO) ())
  :: GHC.Prim.State# GHC.Prim.RealWorld
 - (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
   ~
 GHC.IOBase.IO ())

Main.lit :: GHC.Word.Word8
[GlobalId]
[NoCafRefs
 Str: DmdType m]
Main.lit = GHC.Word.W8# __word 13

Main.lit1 :: GHC.Word.Word8
[GlobalId]
[NoCafRefs
 Str: DmdType m]
Main.lit1 = GHC.Word.W8# __word 10

Main.lit2 :: GHC.Word.Word8
[GlobalId]
[NoCafRefs
 Str: DmdType m]
Main.lit2 = GHC.Word.W8# __word 9

Main.lit3 :: GHC.Word.Word8
[GlobalId]
[NoCafRefs
 Str: DmdType m]
Main.lit3 = GHC.Word.W8# __word 32

Main.isSpaceWord8 :: GHC.Word.Word8 - GHC.Bool.Bool
[GlobalId]
[Arity 1
 NoCafRefs
 Str: DmdType U(L)]
Main.isSpaceWord8 =
  __inline_me (\ (w_ap1 :: GHC.Word.Word8) -
 GHC.Classes.||
   (GHC.Word.==2 w_ap1 Main.lit3)
   (GHC.Classes.||
  (GHC.Word.==2 w_ap1 Main.lit2)
  (GHC.Classes.||
 (GHC.Word.==2 w_ap1 Main.lit1) (GHC.Word.==2 w_ap1
Main.lit

Main.firstnonspace :: GHC.Ptr.Ptr GHC.Word.Word8
  - GHC.Types.Int
  - GHC.Types.Int
  - GHC.Types.Int
[GlobalId]
[Arity 3
 NoCafRefs
 Str: DmdType U(L)U(L)U(L)m]
Main.firstnonspace =
  __inline_me (\ (ds_dGa :: GHC.Ptr.Ptr GHC.Word.Word8)
 (ds1_dGb :: GHC.Types.Int)
 (ds2_dGc :: GHC.Types.Int) -
 case ds_dGa of wild_B1 { GHC.Ptr.Ptr p_ap6 -
 case ds1_dGb of wild1_XB { GHC.Types.I# n_ap8 -
 case ds2_dGc of wild2_XG { GHC.Types.I# m_apa -
 letrec {
   first_sH5 :: GHC.Prim.Addr#
- GHC.Prim.Int#
- GHC.Prim.Int#
- GHC.Prim.Int#
   [Arity 3
Str: DmdType LLL]
   first_sH5 =
 \ (addr_ape :: GHC.Prim.Addr#)
   (n'_apg :: GHC.Prim.Int#)
   (m'_api :: GHC.Prim.Int#) -
   case GHC.Prim.=# n'_apg m'_api of wild3_XS {
 GHC.Bool.False -
   case GHC.Classes.not
  (Main.isSpaceWord8
 (GHC.Word.W8#
(GHC.Prim.indexWord8OffAddr# addr_ape n'_apg)))
   of wild4_XU {
 GHC.Bool.False - first_sH5 addr_ape
(GHC.Prim.+# n'_apg 1) m'_api;
 GHC.Bool.True - n'_apg
   };
 GHC.Bool.True - n'_apg
   }; } in
 case first_sH5 p_ap6 n_ap8 m_apa of wild3_XN { __DEFAULT -
 GHC.Types.I# wild3_XN
 }
   

crash building gtk2hs on win32 using ghc 6.5

2006-07-13 Thread Jason Dagit

[Sorry for the duplicate, I tried to submit this through the trac
interface but the formatting was destroyed by trac so I'm emailing it
in hopes that it preserves some formatting.]

Trying to build gtk2hs-0.9.10 on win32 using ghc 6.5 (the ghc that
ships with visual haskell).

output of ghc -v5:
Glasgow Haskell Compiler, Version 6.5, for Haskell 98, compiled by GHC
version 6.4
Using package config file: c:\Program Files\Visual Haskell\package.conf
name: rts
version: 1.0
license: AllRightsReserved
copyright:
maintainer:
stability:
homepage:
package-url:
description:
category:
author:
exposed: True
exposed-modules:
hidden-modules:
import-dirs:
library-dirs: c:/Program Files/Visual Haskell
 c:/Program Files/Visual Haskell/gcc-lib
hs-libraries: HSrts
extra-libraries: m gmp wsock32
include-dirs: c:/Program Files/Visual Haskell/include
 c:/Program Files/Visual Haskell/include/mingw
includes: Stg.h
depends:
hugs-options:
cc-options:
ld-options: -u _GHCziBase_Izh_static_info -u
   _GHCziBase_Czh_static_info -u _GHCziFloat_Fzh_static_info -u
   _GHCziFloat_Dzh_static_info -u _GHCziPtr_Ptr_static_info -u
   _GHCziWord_Wzh_static_info -u _GHCziInt_I8zh_static_info -u
   _GHCziInt_I16zh_static_info -u _GHCziInt_I32zh_static_info -u
   _GHCziInt_I64zh_static_info -u _GHCziWord_W8zh_static_info -u
   _GHCziWord_W16zh_static_info -u _GHCziWord_W32zh_static_info -u
   _GHCziWord_W64zh_static_info -u _GHCziStable_StablePtr_static_info
   -u _GHCziBase_Izh_con_info -u _GHCziBase_Czh_con_info -u
   _GHCziFloat_Fzh_con_info -u _GHCziFloat_Dzh_con_info -u
   _GHCziPtr_Ptr_con_info -u _GHCziPtr_FunPtr_con_info -u
   _GHCziStable_StablePtr_con_info -u _GHCziBase_False_closure -u
   _GHCziBase_True_closure -u _GHCziPack_unpackCString_closure -u
   _GHCziIOBase_stackOverflow_closure -u
   _GHCziIOBase_heapOverflow_closure -u
   _GHCziIOBase_NonTermination_closure -u
   _GHCziIOBase_BlockedOnDeadMVar_closure -u
   _GHCziIOBase_BlockedIndefinitely_closure -u
   _GHCziIOBase_Deadlock_closure -u
   _GHCziWeak_runFinalizzerBatch_closure
framework-dirs:
frameworks:
haddock-interfaces:
haddock-html:
name: haskell98
version: 1.0
license: AllRightsReserved
copyright:
maintainer:
stability:
homepage:
package-url:
description:
category:
author:
exposed: True
exposed-modules: Array Bits CError CForeign CPUTime CString CTypes
Char Complex Directory ForeignPtr IO Int Ix List Locale
MarshalAlloc MarshalArray MarshalError MarshalUtils
Maybe Monad Ptr
Random Ratio StablePtr Storable System Time Word
hidden-modules:
import-dirs: c:/Program Files/Visual Haskell/imports
library-dirs: c:/Program Files/Visual Haskell
hs-libraries: HShaskell98
extra-libraries:
include-dirs:
includes:
depends: base-1.0
hugs-options:
cc-options:
ld-options:
framework-dirs:
frameworks:
haddock-interfaces: $topdir/html/libraries/haskell98/haskell98.haddock
haddock-html: $topdir/html/libraries/haskell98
name: template-haskell
version: 1.0
license: AllRightsReserved
copyright:
maintainer:
stability:
homepage:
package-url:
description:
category:
author:
exposed: True
exposed-modules: Language.Haskell.TH.PprLib Language.Haskell.TH.Lib
Language.Haskell.TH.Ppr Language.Haskell.TH.Syntax
Language.Haskell.TH
hidden-modules:
import-dirs: c:/Program Files/Visual Haskell/imports
library-dirs: c:/Program Files/Visual Haskell
hs-libraries: HStemplate-haskell
extra-libraries:
include-dirs:
includes:
depends: base-1.0 haskell98-1.0
hugs-options:
cc-options:
ld-options:
framework-dirs:
frameworks:
haddock-interfaces:
$topdir/html/libraries/template-haskell/template-haskell.haddock
haddock-html: $topdir/html/libraries/template-haskell
name: Cabal
version: 1.0
license: AllRightsReserved
copyright:
maintainer:
stability:
homepage:
package-url:
description:
category:
author:
exposed: True
exposed-modules: Distribution.Compat.ReadP Distribution.Compiler
Distribution.Extension Distribution.GetOpt
Distribution.InstalledPackageInfo Distribution.License
Distribution.Make Distribution.Package
Distribution.PackageDescription Distribution.ParseUtils
Distribution.PreProcess Distribution.Setup Distribution.Simple
Distribution.Version Distribution.PreProcess.Unlit
Distribution.Simple.Build Distribution.Simple.Configure
Distribution.Simple.GHCPackageConfig
Distribution.Simple.Install
Distribution.Simple.LocalBuildInfo Distribution.Simple.Register
Distribution.Simple.SrcDist Distribution.Simple.Utils
Language.Haskell.Extension
hidden-modules: Distribution.Compat.Exception
   Distribution.Compat.RawSystem Distribution.Compat.FilePath
   

Re: internal error: scavenge_stack: weird activation record found onstack: 0

2005-09-14 Thread Jason Dagit
Interesting.  I was able to reproduce it on debian using x86.  I also  
noticed that it seemed to be related to the exception handling.  If I  
catch all exceptions at the highest level (that is add one more level  
of exception catching) then the crashing goes away.


Thanks,
Jason

On Sep 14, 2005, at 8:30 AM, Simon Marlow wrote:

I can't repeat this on i386-unknown-linux or x86_64-unknown-linux,  
with

GHC 6.4 or 6.4.1.

Wolfgang, does it happen for you?

Cheers,
Simon

On 21 August 2005 21:24, Jason Dagit wrote:



Hello,

I have discovered that when using forkOS and exitWith that I get the
following error:
hud: internal error: scavenge_stack: weird activation record found on
stack: 0
 Please report this as a bug to glasgow-haskell-bugs@haskell.org,
 or http://www.sourceforge.net/projects/ghc/

I'm using OSX 10.4, and ghc 6.4 from darwinports.

Thanks,
Jason

I have attached a relatively simple program that demonstrates the
crash, here are steps to reproduce the crash:
$ make
ghc -threaded --make Hud.hs -o hud
Chasing modules from: Hud.hs
Compiling Main ( Hud.hs, Hud.o )
Linking ...
ghc -threaded --make Connector.hs -o connector
Chasing modules from: Connector.hs
Compiling Main ( Connector.hs, Connector.o )
Linking ...
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ hud 2000 
[1] 10441
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ telnet localhost 2000
Trying ::1...
telnet: connect to address ::1: Connection refused
Trying 127.0.0.1...
Connected to localhost.
Escape character is '^]'.
Accepted on: {handle: socket: 7}
changing buffering on: {handle: socket: 7}
Connection from localhost on: ThreadId 4
quit
QuitEvent
Connection closed by foreign host.
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ hud: exit: ExitSuccess


[01:20 [EMAIL PROTECTED]/local-data/hud]
$ telnet localhost 2000
Trying ::1...
telnet: connect to address ::1: Connection refused
Trying 127.0.0.1...
Connected to localhost.
Escape character is '^]'.
Accepted on: {handle: socket: 7}
changing buffering on: {handle: socket: 7}
Connection from localhost on: ThreadId 5
hud: internal error: scavenge_stack: weird activation record found on
stack: 0
 Please report this as a bug to glasgow-haskell-bugs@haskell.org,
 or http://www.sourceforge.net/projects/ghc/
Connection closed by foreign host.
[1]+  Exit 254hud 2000






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


internal error: scavenge_stack: weird activation record found on stack: 0

2005-09-12 Thread Jason Dagit

Hello,

I have discovered that when using forkOS and exitWith that I get the  
following error:
hud: internal error: scavenge_stack: weird activation record found on  
stack: 0

Please report this as a bug to glasgow-haskell-bugs@haskell.org,
or http://www.sourceforge.net/projects/ghc/

I'm using OSX 10.4, and ghc 6.4 from darwinports.

Thanks,
Jason

I have attached a relatively simple program that demonstrates the  
crash, here are steps to reproduce the crash:

$ make
ghc -threaded --make Hud.hs -o hud
Chasing modules from: Hud.hs
Compiling Main ( Hud.hs, Hud.o )
Linking ...
ghc -threaded --make Connector.hs -o connector
Chasing modules from: Connector.hs
Compiling Main ( Connector.hs, Connector.o )
Linking ...
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ hud 2000 
[1] 10441
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ telnet localhost 2000
Trying ::1...
telnet: connect to address ::1: Connection refused
Trying 127.0.0.1...
Connected to localhost.
Escape character is '^]'.
Accepted on: {handle: socket: 7}
changing buffering on: {handle: socket: 7}
Connection from localhost on: ThreadId 4
quit
QuitEvent
Connection closed by foreign host.
[01:20 [EMAIL PROTECTED]/local-data/hud]
$ hud: exit: ExitSuccess


[01:20 [EMAIL PROTECTED]/local-data/hud]
$ telnet localhost 2000
Trying ::1...
telnet: connect to address ::1: Connection refused
Trying 127.0.0.1...
Connected to localhost.
Escape character is '^]'.
Accepted on: {handle: socket: 7}
changing buffering on: {handle: socket: 7}
Connection from localhost on: ThreadId 5
hud: internal error: scavenge_stack: weird activation record found on  
stack: 0

Please report this as a bug to glasgow-haskell-bugs@haskell.org,
or http://www.sourceforge.net/projects/ghc/
Connection closed by foreign host.
[1]+  Exit 254hud 2000



hud.tar.gz
Description: GNU Zip compressed data
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs