Re: [GHC] #1391: forkProcess() in Schedule.c with -threaded should initialize mutexes in child process (POSIX)

2007-10-11 Thread GHC
#1391: forkProcess() in Schedule.c with -threaded should initialize mutexes in
child process (POSIX)
---+
Reporter:  thorkilnaur |Owner:  igloo  
Type:  merge   |   Status:  new
Priority:  high|Milestone:  6.8.1  
   Component:  Runtime System  |  Version:  6.7
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
  Os:  MacOS X | Testcase:  forkprocess01(ghci)
Architecture:  powerpc |  
---+
Changes (by simonmar):

  * owner:  simonmar = igloo
  * type:  bug = merge
  * milestone:  6.8 branch = 6.8.1

Comment:

 Following patches need to be merged:

 {{{
 Tue Oct  9 13:24:09 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * also call initMutex on every task-lock, see #1391

 Thu Sep 27 10:13:31 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * also acquire/release task-lock across fork()

 Fri Sep 14 15:55:19 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * attempt to fix #1391, hold locks across fork() and initialize them in
 the ch
 ild
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1391#comment:10
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] #1680: Attempting to do foreign import with unboxed tuple return type causes GHC panic

2007-10-11 Thread GHC
#1680: Attempting to do foreign import with unboxed tuple return type causes GHC
panic
---+
Reporter:  sorear  |Owner:  igloo 
Type:  merge   |   Status:  new   
Priority:  normal  |Milestone:  6.8 branch
   Component:  Compiler (FFI)  |  Version:  6.7   
Severity:  normal  |   Resolution:
Keywords:  |   Difficulty:  Unknown   
  Os:  Linux   | Testcase:  ccfail002 
Architecture:  x86 |  
---+
Changes (by simonpj):

  * testcase:  = ccfail002
  * owner:  = igloo
  * type:  bug = merge

Comment:

 Thanks, excellent point.  Now fixed.  (A one line fix in `TcType`.)

 Ian, please merge
 {{{
 Thu Oct 11 13:34:26 BST 2007  [EMAIL PROTECTED]
   * Fix Trac #1680; check for unboxed tuples in TcType.marshalableTyCon
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1680#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


Re: [GHC] #1767: :show setting does not conform to documented specification

2007-10-11 Thread GHC
#1767: :show setting does not conform to documented specification
+---
Reporter:  guest|Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  GHCi |  Version:  6.9
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Changes (by guest):

 * cc: [EMAIL PROTECTED] (added)

Comment:

 first, you might want to add yourself to the cc of all those tickets you
 create - not only will this earn you an extra copy of each change email
 .., but ghc hq actually uses the number of cc's to assign ticket
 priorities.

 second, the help for :show currently mainly refers to ghci's :set features
 (args, prog, prompt, editor, ..), and 6.9.20070917 gives me this:
 {{{
 Prelude :show args
 []
 Prelude :show prompt
 %s 
 Prelude :show editor
 c:/vim/vim70/gvim.exe
 Prelude :set args 1 two
 Prelude :show args
 [1,two]
 }}}

 third, it would be nice if all option/flag settings were available.
 there's a patch pending for head that makes ':set' show dynamic flag
 settings, with special emphasis on the ghci-specific ones. it also adds
 ':show languages' (listing active language flags) and ':show packages'
 (listing active package flags, and currently loaded packages). that still
 leaves lots of options like -l -i, etc, but it's a small step in the right
 direction.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1767#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] #95: GHCi editor binding with :e

2007-10-11 Thread GHC
#95: GHCi editor binding with :e
+---
Reporter:  martijnislief|Owner:  nobody 
Type:  feature request  |   Status:  assigned   
Priority:  normal   |Milestone:  6.8 branch 
   Component:  GHCi |  Version:  None   
Severity:  minor|   Resolution:  None   
Keywords:   |   Difficulty:  Easy (1 hr)
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Comment (by guest):

 actually, it turns out you can define all this even back in 6.4.1 (had i
 only known back then!-). you need to define your own :e command (:def is
 available), and ghci 6.4.1 is somewhat annoying about command names that
 are prefixes of each other. have a look at

 http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/dot-
 squashed.ghci641

 http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/dot-
 squashed.ghci

 since .ghci files are not very readable with definitions squashed into
 single lines, you might want to check the explanations of the latter file
 in

 http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html

 (note: the names in the 6.4.1 version differ from those in the described
 version)

 i'm not yet sure whether being able to define :e means that it shouldn't
 be part of ghci at all (and this ticket be closed), or whether there are
 still any advantages to having it built in? perhaps ghci releases should
 have a selection of .ghci files with useful definitions?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/95#comment:7
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] #1772: GHC doesn't like 'inline' type function applications

2007-10-11 Thread GHC
#1772: GHC doesn't like 'inline' type function applications
--+-
  Reporter:  jpbernardy   |  Owner: 
  Type:  bug  | Status:  new
  Priority:  normal   |  Milestone:  6.8.1  
 Component:  Compiler (Type checker)  |Version:  6.9
  Severity:  normal   |   Keywords: 
Difficulty:  Unknown  | Os:  Unknown
  Testcase:   |   Architecture:  Unknown
--+-
 {{{
 {-# LANGUAGE TypeFamilies #-}

 import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
 elem, notElem, concat, concatMap, and, or, any, all,
 sum, product, maximum, minimum)
 import Data.Monoid

 type family Element t

 class Foldable t where
 foldMap :: Monoid m = (Element t - m) - t - m

 foldr :: (Element t - b - b) - b - t - b
 -- foldr :: Element t ~ a = (a - b - b) - b - t - b
 foldr f z t = appEndo (foldMap (Endo . f) t) z
 }}}
 GHC chokes on the above module. If the signature of foldr is replaced by
 the commented one, GHC is happy. It seems to me that the two expressions
 should be equivalent.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1772
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