[GHC] #7159: CoreToStg.coreToStgArgs fails when CoreToStg.coreToStg is called

2012-08-18 Thread GHC
#7159: CoreToStg.coreToStgArgs fails when CoreToStg.coreToStg is called
-+--
 Reporter:  guest|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  GHC API
  Version:  7.4.1|   Keywords: 
   Os:  Linux|   Architecture:  x86
  Failure:  Incorrect result at runtime  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--
 Not much more to say than the title. It said Panic! (the 'impossible'
 happened), and to report it as a bug.

 The file typescript in the attached tarball gives the version and
 all the information from ghc --info, as well as a demonstration of
 the failure. The tarball also contains the program and test case that
 failed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7159
GHC http://www.haskell.org/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] #7159: CoreToStg.coreToStgArgs fails when CoreToStg.coreToStg is called

2012-08-18 Thread GHC
#7159: CoreToStg.coreToStgArgs fails when CoreToStg.coreToStg is called
---+
Reporter:  guest   |Owner: 
Type:  bug |   Status:  closed 
Priority:  normal  |Component:  GHC API
 Version:  7.4.1   |   Resolution:  invalid
Keywords:  |   Os:  Linux  
Architecture:  x86 |  Failure:  Incorrect result at runtime
Testcase:  |Blockedby: 
Blocking:  |  Related: 
---+
Changes (by guest):

  * status:  new = closed
  * resolution:  = invalid


Comment:

 This is not a bug after all. I needed to use CorePrep.corePrepPgm before
 trying to use CoreToStg.coreToStg. I suppose the lack of documentation
 could be called a bug, but since the internals are in constant flux, I'm
 not surprised that nobody bothers to write any.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7159#comment:1
GHC http://www.haskell.org/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] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2012-08-18 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  _|_ 
   Component:  Compiler  | Version:  6.10.2  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by singpolyma):

 I'm strongly considering using CPP and #include to work around this
 problem in my most recent project.

 The problem I have is both the duplication of information in two places
 (very un-DRY) and having to pick a place to break the import cycle.  I
 understand that doing this cross-package (if that even ever makes sense at
 all) would be very complex, but I think what most people here (correct me
 if I'm wrong) are interested in is the case where all the source for all
 the modules is in one project and thus can be build with a single GHC
 invocation.

 Since pasting the contents of one module into the top of another instead
 of importing it works (hence my thoughts about CPP and #include) the way
 forward seems to be: treat all modules in a cycle as a single module with
 multiple names/export lists.  That way the compiler has no problem (since
 it can compile all these as one module already, if I paste all the code
 together) and imports of any of the modules into *other* modules would
 still work (since GHC would just pick which things to import/can be
 imported from the mega-module based on which of its names was used).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1409#comment:53
GHC http://www.haskell.org/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] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2012-08-18 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  _|_ 
   Component:  Compiler  | Version:  6.10.2  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by singpolyma):

 * cc: singpolyma@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1409#comment:54
GHC http://www.haskell.org/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] #7160: C finalizers are reversed during GC

2012-08-18 Thread GHC
#7160: C finalizers are reversed during GC
-+--
 Reporter:  int-e|  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Runtime System  
  Version:  7.6.1-rc1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 (See also thread starting at
 http://www.haskell.org/pipermail/libraries/2012-August/018302.html )

 The list of finalizers is reversed during GC (cf.
 {{{rts/sm/MarkWeak.c}}}), which may cause them to run in the wrong order.
 The following program reproduces this behaviour.

 {{{
 {-# LANGUAGE ForeignFunctionInterface, MagicHash #-}
 import GHC.ForeignPtr
 import GHC.Ptr
 import System.Mem

 -- one should really use own C function rather than this varargs one to
 avoid
 -- possible ABI issues
 foreign import ccall debugBelch fun :: FunPtr (Ptr () - Ptr () - IO
 ())

 new name = do
 p - newForeignPtr_ (Ptr name)
 addForeignPtrFinalizerEnv fun (Ptr finalizer 1 (%s)\n#) p
 addForeignPtrFinalizerEnv fun (Ptr finalizer 2 (%s)\n#) p
 return p

 main = do
 p - new p#
 q - new q#
 r - new r#
 performGC -- collect p. finalizer order: 2, then 1.
 print q
 performGC -- collect q. finalizer order: 1, then 2.
   -- expected order: 2, then 1.
 print r
 performGC -- collect r. finalizer order: 2, then 1.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7160
GHC http://www.haskell.org/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] #7160: C finalizers are reversed during GC

2012-08-18 Thread GHC
#7160: C finalizers are reversed during GC
-+--
 Reporter:  int-e|  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Runtime System  
  Version:  7.6.1-rc1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by Lemming):

 The above code crashes on my machine but I could easily add some C
 functions that do the job. You may run the code with
 $ ghc FinalizerOrderC.c FinalizerOrder.hs
 $ ./FinalizerOrder
 0x7f67f77fc010
 finalize 2 7f67f77fc010
 finalize 1 7f67f77fc010
 0x7f67f77fc040
 finalize 1 7f67f77fc040
 finalize 2 7f67f77fc040
 0x7f67f77fc060
 finalize 2 7f67f77fc060
 finalize 1 7f67f77fc060

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7160#comment:1
GHC http://www.haskell.org/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] #7160: C finalizers are reversed during GC

2012-08-18 Thread GHC
#7160: C finalizers are reversed during GC
-+--
 Reporter:  int-e|  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Runtime System  
  Version:  7.6.1-rc1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by Lemming):

 {{{
 $ ghc FinalizerOrderC.c FinalizerOrder.hs
 [1 of 1] Compiling Main ( FinalizerOrder.hs, FinalizerOrder.o
 )
 Linking FinalizerOrder ...
 $ ./FinalizerOrder
 0x7f67f77fc010
 finalize 2 7f67f77fc010
 finalize 1 7f67f77fc010
 0x7f67f77fc040
 finalize 1 7f67f77fc040
 finalize 2 7f67f77fc040
 0x7f67f77fc060
 finalize 2 7f67f77fc060
 finalize 1 7f67f77fc060
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7160#comment:2
GHC http://www.haskell.org/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] #7161: hSetNewlineMode and hSetEncoding can be performed on closed and semi-closed handles

2012-08-18 Thread GHC
#7161: hSetNewlineMode and hSetEncoding can be performed on closed and 
semi-closed
handles
--+-
 Reporter:  duncan|  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  libraries/base  
  Version:  7.6.1-rc1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 The `hSetNewlineMode` and `hSetEncoding` functions from `GHC/IO/Handle.hs`
 do not check that the Handle is in an open mode. It is possible to use
 them on closed handles. hSetEncoding on a closed Handle triggers a
 segfault. Similarly, the operations are also both possible on semi-closed
 handles, and given the way hGetContents is implemented, this will affect
 the result of hGetContents which is clearly against the intention of the
 hGetContents/semi-closed stuff.

 Both functions use the `withAllHandles__` helper. Unlike similar helpers
 like `wantReadableHandle_` this one doesn't do any handle mode checking.

 Additionally, `hSetBuffering` and `hSetBinary` mode also use the
 `withAllHandles__` pattern and don't obviously check for an open handle
 but I've not verified this.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7161
GHC http://www.haskell.org/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] #7162: RULES that never fire (automatically)

2012-08-18 Thread GHC
#7162: RULES that never fire (automatically)
--+-
 Reporter:  andygill  |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.4.2 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 We want a way of having GHC RULES known by GHC, but not used by the
 optimizer.

 HERMIT, a interactive plugin for GHC that applies rules - and as well as
 built in rules (like alpha conversion, beta-reduction, etc) - also provide
 access to the named GHC RULES. Here is the rub: We want to use GHC RULES
 that are parsed and typed checked like normal rules, are visible to the
 HERMIT system, but never run by the simplifier. Currently we can say
  - attempt this *before* this (opt) pass, or
  - attempt *after* this pass, there is no way of saying
  - *never* attempt.

 We were thinking

 {-# RULES [~] map/map forall f g . map f (map g xs) = map (f.g) xs
 #-}

 Where the [~] says *never* execute this without be explicitly asked,
 following on from the [~0] which does not run in first pass.

 We happy making the required changes.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7162
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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