Re: [GHC] #4251: GHC hangs during Network.HTTP.simpleHTTP on Windows XP SP3, Windows 7

2010-08-18 Thread GHC
#4251: GHC hangs during Network.HTTP.simpleHTTP on Windows XP SP3, Windows 7
--+-
  Reporter:  balta2ar |  Owner:  igloo   
  Type:  bug  | Status:  closed  
  Priority:  high |  Milestone:  6.14.1  
 Component:  libraries (other)|Version:  6.12.3  
Resolution:  invalid  |   Keywords:  hang, simplehttp
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Windows 
  Blocking:   |   Architecture:  x86 
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by balta2ar):

 So how do I avoid looping on the specified OSes and make it working?

-- 
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] #4250: make install fails with the head version of GHC

2010-08-18 Thread GHC
#4250: make install fails with the head version of GHC
+---
  Reporter:  maa|  Owner:  igloo 
  Type:  bug| Status:  closed
  Priority:  normal |  Milestone:
 Component:  Build System   |Version:  6.13  
Resolution:  fixed  |   Keywords:
  Testcase: |  Blockedby:
Difficulty: | Os:  Linux 
  Blocking: |   Architecture:  x86_64 (amd64)
   Failure:  Installing GHC failed  |  
+---
Changes (by igloo):

  * status:  new => closed
  * resolution:  => fixed


Comment:

 Thanks for the report; fixed.

-- 
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] #915: Implement list fusion using streams instead of foldr/build

2010-08-18 Thread GHC
#915: Implement list fusion using streams instead of foldr/build
-+--
Reporter:  simonpj   |Owner:
Type:  task  |   Status:  new   
Priority:  low   |Milestone:  6.14.1
   Component:  libraries/base|  Version:  6.8   
Keywords:  fusion| Testcase:  N/A   
   Blockedby:|   Difficulty:  Project (more than a week)
  Os:  Unknown/Multiple  | Blocking:
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown  
-+--
Changes (by Remi):

 * cc: rt...@… (added)


-- 
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] #4262: GHC's runtime never terminates unused worker threads

2010-08-18 Thread GHC
#4262: GHC's runtime never terminates unused worker threads
-+--
Reporter:  Remi  |   Owner: 
 
Type:  bug   |  Status:  new
 
Priority:  normal|   Component:  Runtime System 
 
 Version:  6.12.3|Keywords:  worker thread foreign function 
interface
Testcase:|   Blockedby: 
 
  Os:  Unknown/Multiple  |Blocking: 
 
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
 
-+--
 When concurrently calling safe FFI functions, worker OS threads are
 created. These threads then never quit.

 The following toy program creates 30k OS threads (which is fine because
 that's exactly what it asks for) which are then never "garbage collected":
 30k threads and over 230g of VM are hanging around until the program
 exits.

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}
 module Main where

 import Control.Concurrent
 import Control.Monad
 import Foreign.C.Types
 import System.Mem

 foreign import ccall safe sleep :: CUInt -> IO ()

 main = do
 replicateM_ 3 $ forkIO $ sleep 2
 getLine
 -- do other stuff
 }}}

 P.S. Of course I should simply use threadDelay in this case. The real
 program performs up to a few hundred concurrent fdatasync calls.

-- 
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] #4250: make install fails with the head version of GHC

2010-08-18 Thread GHC
#4250: make install fails with the head version of GHC
---+
Reporter:  maa |Owner:  igloo
Type:  bug |   Status:  new  
Priority:  normal  |Milestone:   
   Component:  Build System|  Version:  6.13 
Keywords:  | Testcase:   
   Blockedby:  |   Difficulty:   
  Os:  Linux   | Blocking:   
Architecture:  x86_64 (amd64)  |  Failure:  Installing GHC failed
---+
Changes (by igloo):

  * owner:  => igloo


-- 
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] #2965: GHC on OS X does not compile 64-bit

2010-08-18 Thread GHC
#2965: GHC on OS X does not compile 64-bit
+---
Reporter:  Axman6   |Owner:  igloo
Type:  feature request  |   Status:  new  
Priority:  normal   |Milestone:  6.14.1   
   Component:  Compiler |  Version:   
Keywords:  64bit| Testcase:   
   Blockedby:   |   Difficulty:  Unknown  
  Os:  MacOS X  | Blocking:   
Architecture:  x86_64 (amd64)   |  Failure:  Installing GHC failed
+---
Changes (by mndrix):

 * cc: mich...@… (added)


-- 
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] #4163: Make cross-compilation work

2010-08-18 Thread GHC
#4163: Make cross-compilation work
-+--
Reporter:  simonmar  |Owner:  
Type:  task  |   Status:  new 
Priority:  high  |Milestone:  6.14.2  
   Component:  Build System  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  Difficult (2-5 days)
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by mndrix):

 * cc: mich...@… (added)


-- 
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] #4251: GHC hangs during Network.HTTP.simpleHTTP on Windows XP SP3, Windows 7

2010-08-18 Thread GHC
#4251: GHC hangs during Network.HTTP.simpleHTTP on Windows XP SP3, Windows 7
--+-
  Reporter:  balta2ar |  Owner:  igloo   
  Type:  bug  | Status:  closed  
  Priority:  high |  Milestone:  6.14.1  
 Component:  libraries (other)|Version:  6.12.3  
Resolution:  invalid  |   Keywords:  hang, simplehttp
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Windows 
  Blocking:   |   Architecture:  x86 
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  new => closed
  * resolution:  => invalid


Comment:

 I don't think this is a GHC bug. This seems to be what's happening:

 `readLineBS` calls `bufferReadLine` which, when it fails at EOF, calls
 `close`, `closeIt`, `closeConnection`, `suck`, `readL`, `readLineBS`.
 Loop.

-- 
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] #2301: Proper handling of SIGINT/SIGQUIT

2010-08-18 Thread GHC
#2301: Proper handling of SIGINT/SIGQUIT
---+
  Reporter:  duncan|   Type:  bug  
Status:  new   |   Priority:  normal   
 Milestone:  6.14.1|  Component:  libraries/process
   Version:  6.8.2 |   Keywords:   
  Testcase:|  Blockedby:   
Difficulty:  Unknown   | Os:  Unknown/Multiple 
  Blocking:|   Architecture:  Unknown/Multiple 
   Failure:  None/Unknown  |  
---+

Comment(by phunge0):

 Replying to [comment:9 diego]:
 > And when describing exec POSIX says:
 > > Signals set to the default action (SIG_DFL) in the calling process
 image shall be set to the default action in the new process image.
 > > Except for SIGCHLD, signals set to be ignored (SIG_IGN) by the calling
 process image shall be set to be ignored by the new process image.
 > > Signals set to be caught by the calling process image shall be set to
 the default action in the new process image (see ).
 >
 > Thus, to avoid breaking applications that rely on the the default
 handler of SIGPIPE the RTS should restore the handler before starting new
 processes.
 >
 > I can't say how many applications are affected by this nowadays. Simple
 applications may rely on default bahavior of signals. But it seems to be a
 minor issue.

 I think this detail needs fixing too, here's a patch as an RFC:
 http://www.haskell.org/pipermail/glasgow-haskell-
 users/2010-August/019082.html

-- 
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] #4209: LLVM: Vector code segfaults under OSX

2010-08-18 Thread GHC
#4209: LLVM: Vector code segfaults under OSX
---+
Reporter:  dterei  |Owner:  dterei   
Type:  bug |   Status:  new  
Priority:  normal  |Milestone:  6.14.1   
   Component:  Compiler (LLVM) |  Version:  6.13 
Keywords:  osx tntc llvm segfault  | Testcase:   
   Blockedby:  |   Difficulty:   
  Os:  MacOS X | Blocking:   
Architecture:  x86 |  Failure:  Runtime crash
---+

Comment(by Lennart):

 This is probably due to memory Haskell allocation not respecting the
 alignment asked for by Storable.  But I think that's been fixed now.

-- 
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] #4261: Add strict version of foldlWithKey to Map

2010-08-18 Thread GHC
#4261: Add strict version of foldlWithKey to Map
-+--
Reporter:  tibbe |   Owner:   
Type:  proposal  |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:|Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--
 There's currently no strict left (pre-order) fold for `Map`s, making it
 impractical to do simple things like summing all the values in the map.
 The attached patch adds a strict `foldlWithKeys'` function that generates
 optimal core for code like:

 {{{
 module Test (test) where

 import qualified Data.Map as M

 test :: M.Map Int Int -> Int
 test m = M.foldlWithKey' (\n k v -> n + k + v) 0 m
 }}}

 If we look at the core we see that the `Int` accumulator is unboxed like
 we'd hope:

 {{{
 test_$s$wgo2 :: Data.Map.Map Int Int -> Int# -> Int#
 test_$s$wgo2 =
   \ (sc_smi :: Data.Map.Map Int Int)
 (sc1_smj :: Int#) ->
 case sc_smi of _ {
   Data.Map.Tip -> sc1_smj;
   Data.Map.Bin _ kx_ali x_alj l_alk r_all ->
 case test_$s$wgo2 l_alk sc1_smj of ww_slW { __DEFAULT ->
 case kx_ali of _ { I# y_alD ->
 case x_alj of _ { I# y1_XlT ->
 test_$s$wgo2
   r_all (+# (+# ww_slW y_alD) y1_XlT)
 }
 }
 }
 }

 $wtest :: Data.Map.Map Int Int -> Int#
 $wtest =
   \ (w_slZ :: Data.Map.Map Int Int) ->
 test_$s$wgo2 w_slZ 0

 test :: Data.Map.Map Int Int -> Int
 test =
   __inline_me (\ (w_slZ :: Data.Map.Map Int Int) ->
  case $wtest w_slZ of ww_sm2 { __DEFAULT ->
  I# ww_sm2
  })
 }}}

 Discussion deadline: 2 weeks

-- 
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] #4210: LLVM: Dynamic Library Support

2010-08-18 Thread GHC
#4210: LLVM: Dynamic Library Support
-+--
Reporter:  dterei|Owner:  dterei   
Type:  feature request   |   Status:  new  
Priority:  normal|Milestone:  6.14.1   
   Component:  Compiler (LLVM)   |  Version:  6.13 
Keywords:| Testcase:   
   Blockedby:|   Difficulty:   
  Os:  Unknown/Multiple  | Blocking:   
Architecture:  Unknown/Multiple  |  Failure:  Runtime crash
-+--

Comment(by dterei):

 Have enabled support for -fPIC and -dynamic on Linux x64, for other
 platforms have changed DynFlags.hs to issue a warning and drop -fllvm if
 -dynaimc or -fPIC are also present.

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