Re: [GHC] #7216: Compositional blocking on file descriptors

2013-01-01 Thread GHC
#7216: Compositional blocking on file descriptors
---+
  Reporter:  AndreasVoellmy|  Owner:  igloo   
  Type:  feature request   | Status:  patch   
  Priority:  normal|  Milestone:  7.8.1   
 Component:  libraries/base|Version:  7.4.2   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by igloo):

 I'm a bit confused. Do these functions work on Windows? In
 Control.Concurrent they just raise an exception on Windows, but it looks
 like in GHC.Conc.IO they are defined on Windows.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7216#comment:12
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] #7540: Panic on type inference with vectorised parallel arrays

2013-01-01 Thread GHC
#7540: Panic on type inference with vectorised parallel arrays
---+
Reporter:  tinctorius  |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Compiler
 Version:  7.6.1   |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by tinctorius):

 An even simpler example:
 {{{
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE ParallelArrays #-}
 module Y where

 import Data.Array.Parallel

 #ifndef BUG
 func :: Bool - [:[:a:]:]
 #endif
 func True = [:[::]:]
 func False = func True
 }}}

 Taking `[:[::]:]` out to its own variable doesn't change a thing, unless
 it's given a monomorphic type signature.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7540#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] #7540: Panic on type inference with vectorised parallel arrays

2013-01-01 Thread GHC
#7540: Panic on type inference with vectorised parallel arrays
-+--
Reporter:  tinctorius|   Owner:  chak  
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.8.1 
   Component:  Compiler  | Version:  7.6.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = chak
  * difficulty:  = Unknown
  * priority:  normal = highest
  * milestone:  = 7.8.1


Comment:

 Thank you!  Yes, I see this happening in HEAD, with `-fvectorise`.
 Manuel, you are rewriting the vectoriser. Might you look at this?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7540#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] #4144: Exception: ToDo: hGetBuf - when using custom handle infrastructure

2013-01-01 Thread GHC
#4144: Exception: ToDo: hGetBuf - when using custom handle infrastructure
---+
  Reporter:  AntoineLatter |  Owner:  simonmar
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  libraries/base|Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * owner:  joeyadams = simonmar
  * difficulty:  = Unknown


Comment:

 Simon M, you look like the most plausible reviewer, since you did the
 earlier patch.

 Simon

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


Re: [GHC] #4144: Exception: ToDo: hGetBuf - when using custom handle infrastructure

2013-01-01 Thread GHC
#4144: Exception: ToDo: hGetBuf - when using custom handle infrastructure
---+
  Reporter:  AntoineLatter |  Owner:  simonmar
  Type:  bug   | Status:  patch   
  Priority:  high  |  Milestone:  7.8.1   
 Component:  libraries/base|Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * priority:  normal = high
  * status:  new = patch
  * milestone:  = 7.8.1


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4144#comment:8
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] #7510: Immediate seg-fault on 32-bit windows build

2013-01-01 Thread GHC
#7510: Immediate seg-fault on 32-bit windows build
-+--
Reporter:  simonpj   |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = simonmar


Comment:

 Thanks Joey!  Simon M: since you made the commit, might you look at Joey's
 analysis?  If he's right the solution should be easy.

 It's quite urgent to fix this, since it utterly breaks the Windows build.

 Thanks

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7510#comment:5
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] #7541: Unavoidable duplicate constraint warning

2013-01-01 Thread GHC
#7541: Unavoidable duplicate constraint warning
--+-
Reporter:  blamario   |  Owner: 
 
Type:  bug| Status:  new
 
Priority:  normal |  Component:  Compiler   
 
 Version:  7.6.1  |   Keywords: 
 
  Os:  Unknown/Multiple   |   Architecture:  
Unknown/Multiple
 Failure:  Incorrect warning at compile-time  |  Blockedby: 
 
Blocking: |Related: 
 
--+-
 The duplicate constraint warning can be triggered in a context where
 it's impossible to remove it, because the constraints come with a type
 synonym.

 The following standalone little module reproduces the problem:

 {{{
 {-# LANGUAGE FlexibleContexts, Rank2Types #-}

 module Test where

 type Constrained x y r = (Eq x, Eq y) = x - y - r

 f :: Constrained String String ()
 f = undefined
 }}}

 The warning is

 {{{
 Test.hs:7:6: Warning:
 Duplicate constraint(s): Eq String
 In the type signature for `f': f :: Constrained String String ()
 }}}

 The warning is present in 7.4.1 and 7.6.1, and presumably in the versions
 between as well.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7541
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] #7510: Immediate seg-fault on 32-bit windows build

2013-01-01 Thread GHC
#7510: Immediate seg-fault on 32-bit windows build
-+--
Reporter:  simonpj   |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by igloo):

 Should we make newtypes of Int called Bytes and Words, so the typechecker
 can stop this sort of problem from occurring in the future?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7510#comment:6
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] #7510: Immediate seg-fault on 32-bit windows build

2013-01-01 Thread GHC
#7510: Immediate seg-fault on 32-bit windows build
-+--
Reporter:  simonpj   |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 Perhaps.  We define type synonyms `ByteOff` and `WordOff` in `SMRep` for
 this purpose, and they are very effective as documentation though not
 enforced.  I'm really not sure how much extra clutter `newtype`s would
 introduce.

 The first thing is to fix the bug though!

 Simon

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


Re: [GHC] #7534: allocateRegsAndSpill: Cannot read from uninitialized register

2013-01-01 Thread GHC
#7534: allocateRegsAndSpill: Cannot read from uninitialized register
--+-
Reporter:  erikd  |   Owner:  simonmar   
Type:  bug|  Status:  new
Priority:  normal |   Milestone: 
   Component:  Compiler   | Version:  7.7
Keywords: |  Os:  Linux  
Architecture:  powerpc64  | Failure:  Building GHC failed
  Difficulty:  Unknown|Testcase: 
   Blockedby: |Blocking: 
 Related: |  
--+-
Changes (by simonpj):

  * owner:  = simonmar
  * difficulty:  = Unknown


Comment:

 Simon M, could this be anything to do with the new codegen path?  I'll
 asssign it to you for now.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7534#comment:3
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] #7290: Minor documentation fix for directory

2013-01-01 Thread GHC
#7290: Minor documentation fix for directory
+---
Reporter:  SimonHengel  |   Owner:   
Type:  bug  |  Status:  merge
Priority:  normal   |   Milestone:   
   Component:  libraries/directory  | Version:  7.6.1
Keywords:   |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple | Failure:  Documentation bug
  Difficulty:  Unknown  |Testcase:   
   Blockedby:   |Blocking:   
 Related:   |  
+---
Changes (by igloo):

  * status:  patch = merge
  * difficulty:  = Unknown


Comment:

 Applied, thanks

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7290#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] #7466: [PATCH] integer-gmp silently ignores --with-gmp-* whenever it finds GMP.framework in the system-standard path

2013-01-01 Thread GHC
#7466: [PATCH] integer-gmp silently ignores --with-gmp-* whenever it finds
GMP.framework in the system-standard path
+---
  Reporter:  PHO|  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  libraries (other)  |Version:  7.6.1   
Resolution:  fixed  |   Keywords:  
Os:  MacOS X|   Architecture:  Unknown/Multiple
   Failure:  Other  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by igloo):

  * status:  patch = closed
  * resolution:  = fixed


Comment:

 Fixed by:
 {{{
 commit 2cf2423a0c0c1e6495812467deee4df0cb4320fa
 Author: Ian Lynagh i...@well-typed.com
 Date:   Tue Jan 1 17:01:00 2013 +

 Provide a way for OS X users to indicate a preference for the GMP
 framework

 We used to always use the framework if it existed. Now the make
 variable
 GMP_PREFER_FRAMEWORK can be used to control whether the library or the
 framework is preferred.

 Fixes #7466.
 }}}
 {{{
 commit d86166d5ca901eb339c4f1f5aca4d636ee86d91f
 Author: Ian Lynagh ig...@earth.li
 Date:   Tue Jan 1 18:41:51 2013 +

 Fix configure when we don't have a gmp library
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7466#comment:5
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] #7542: GHC doesn't optimize (strict) composition with id

2013-01-01 Thread GHC
#7542: GHC doesn't optimize (strict) composition with id
+---
Reporter:  shachaf  |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  Compiler
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Runtime performance bug  |  Blockedby:  
Blocking:   |Related:  
+---
 Newtype constructors and selectors have no runtime overhead, but some uses
 of them do. For example, given `newtype Identity a = Identity {
 runIdentity :: a }`, `Identity` turns into `id`, but `Identity . f` turns
 into `id . f`, which is distinct from `f`, because it gets eta-expanded to
 `\x - f x`.

 It would be nice to be able to compose a newtype constructor with a
 function without any overhead. The obvious thing to try is strict
 composition:

 {{{
 (#) :: (b - c) - (a - b) - a - c
 (#) f g = f `seq` g `seq` \x - f (g x)
 }}}

 In theory this should get rid of the eta-expansion. In practice, the
 generated Core looks like this:

 {{{
 foo :: (a - b) - [a] - [b]
 foo f = map (id # f)
 -- becomes
 foo = \f e - map (case f of g { __DEFAULT - \x - g x }) e
 }}}

 Different variations of `(#)`, and turning `-fpedantic-bottoms` on, don't
 seem to affect this. A simpler version, `foo f = map (f `seq` \x - f x)`,
 generates the same sort of Core.

 In one library we resorted to defining a bunch of functions of the form
 `identityDot :: (a - b) - a - Identity b; identityDot = unsafeCoerce`.
 It would be better to be able to rely on GHC to do the optimization
 directly, if we use strict composition anyway.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7542
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] #7216: Compositional blocking on file descriptors

2013-01-01 Thread GHC
#7216: Compositional blocking on file descriptors
---+
  Reporter:  AndreasVoellmy|  Owner:  igloo   
  Type:  feature request   | Status:  patch   
  Priority:  normal|  Milestone:  7.8.1   
 Component:  libraries/base|Version:  7.4.2   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by AndreasVoellmy):

 I think the confusion also exists for the threadWaitRead and
 threadWaitWrite functions. They are defined in GHC.Conc.IO even for
 Windows, but then they seem to be completely ignored in Control.Concurrent
 and the functions of the same name there are defined for Windows only in
 the threaded RTS (or for stdin in non-threaded RTS).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7216#comment:13
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] #7361: Segmentation fault on 5f37e0c71ff4af8539c5aebc739b006b4f0c6ebf

2013-01-01 Thread GHC
#7361: Segmentation fault on 5f37e0c71ff4af8539c5aebc739b006b4f0c6ebf
-+--
Reporter:  bgamari   |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.7 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Runtime crash   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by bgamari):

 It seems this can still be reproduced with
 `db9c062a4a7c39563a3a9a83718cc0ce6d4babae`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7361#comment:20
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] #7543: Constraint synonym instances

2013-01-01 Thread GHC
#7543: Constraint synonym instances
-+--
Reporter:  monoidal  |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 It would be great if GHC could compile:

 {{{
 {-# LANGUAGE ConstraintKinds #-}

 type Ring = Num

 instance Ring [a] where
   (+) = (++)
 }}}

 Currently this gives an error: `(+)` is not a visible method of class
 `Ring`. After removing the last line, the code compiles with warnings
 about missing methods.

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