Re: [GHC] #6065: Suggested type signature causes a type error (even though it appears correct)

2012-06-04 Thread GHC
#6065: Suggested type signature causes a type error (even though it appears
correct)
---+
 Reporter:  tvynr  |  Owner:
  
 Type:  bug| Status:  new   
  
 Priority:  normal |  Component:  Compiler (Type 
checker) 
  Version:  7.4.1  |   Keywords:  type signature 
typeclass instance forall
   Os:  Linux  |   Architecture:  x86_64 (amd64)
  
  Failure:  GHC rejects valid program  |   Testcase:
  
Blockedby: |   Blocking:
  
  Related: |  
---+

Comment(by guest):

 I reduced your test case. The following file compiles, but if inferred
 type signature to "upcast" is added, it doesn't.

 {{{
 {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances
 #-}

 class AstOp ast result where
   astop :: ast -> result

 -- upcast :: AstOp ast ((ast -> t) -> t) => ast -> t
 upcast ast = astop ast upcast
 }}}

-- 
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] #6142: Outdated comment in Directory.hs

2012-06-04 Thread GHC
#6142: Outdated comment in Directory.hs
---+
 Reporter:  mjo|  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Component:  libraries/directory
  Version: |   Keywords: 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple   
  Failure:  Documentation bug  |   Testcase: 
Blockedby: |   Blocking: 
  Related: |  
---+
 The signature for `getModificationTime` has been updated to `FilePath ->
 IO UTCTime`, but the export list still has a comment mentioning `IO
 ClockTime`.

-- 
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] #6141: ghc: panic! (the 'impossible' happened)

2012-06-04 Thread GHC
#6141: ghc: panic! (the 'impossible' happened)
---+
Reporter:  aSect   |Owner:   
Type:  bug |   Status:  closed   
Priority:  normal  |Component:  Compiler 
 Version:  7.4.1   |   Resolution:  invalid  
Keywords:  |   Os:  Linux
Architecture:  x86_64 (amd64)  |  Failure:  GHC rejects valid program
Testcase:  |Blockedby:   
Blocking:  |  Related:   
---+

Comment(by guest):

 It was fixed by #5961.

-- 
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] #6104: Regression: space leak in HEAD vs. 7.4

2012-06-04 Thread GHC
#6104: Regression: space leak in HEAD vs. 7.4
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.5 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Compile-time performance bug
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by pcapriotti):

  * owner:  pcapriotti =>


Comment:

 Here are some heap profiler reports comparing GHC HEAD with 7.4 when
 compiling
 Cabal and the single Cabal module Distribution/Simple/Setup.hs.

 They are obtained by running:

 {{{
 ghc -O --make Distribution.Simple +RTS -hc
 }}}

 and

 {{{
 ghc -O -fforce-recomp --make Distribution/Simple/Setup.hs +RTS -hc
 }}}

 respectively, with both compilers built with `-prof -auto` on
 `compiler/simplCore/Simplify.lhs`, where the leak seems to be located.

-- 
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] #4413: (^^) is not correct for Double and Float

2012-06-04 Thread GHC
#4413: (^^) is not correct for Double and Float
--+-
Reporter:  daniel.is.fischer  |   Owner:  tcsavage  
 
Type:  bug|  Status:  new   
 
Priority:  low|   Milestone:  7.6.1 
 
   Component:  libraries/base | Version:  7.1   
 
Keywords:  Double, Float, exponentiation  |  Os:  Unknown/Multiple  
 
Architecture:  Unknown/Multiple   | Failure:  Incorrect result 
at runtime
  Difficulty: |Testcase:
 
   Blockedby: |Blocking:
 
 Related: |  
--+-
Changes (by tcsavage):

  * owner:  => tcsavage


-- 
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] #6133: bad error message when incorrect format package db is supplied

2012-06-04 Thread GHC
#6133: bad error message when incorrect format package db is supplied
-+--
  Reporter:  gfxmonk |  Owner:  pcapriotti  
  Type:  bug | Status:  closed  
  Priority:  normal  |  Milestone:  
 Component:  ghc-pkg |Version:  7.0.4   
Resolution:  fixed   |   Keywords:  
Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
   Failure:  Compile-time crash  | Difficulty:  Unknown 
  Testcase:  |  Blockedby:  
  Blocking:  |Related:  
-+--
Changes (by pcapriotti):

  * status:  new => closed
  * resolution:  => 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] #6133: bad error message when incorrect format package db is supplied

2012-06-04 Thread GHC
#6133: bad error message when incorrect format package db is supplied
-+--
Reporter:  gfxmonk   |   Owner:  pcapriotti
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:
   Component:  ghc-pkg   | Version:  7.0.4 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by p.capriotti@…):

 commit 50fddb2b046605315f903d9b744780497cc978de
 {{{
 Author: Paolo Capriotti 
 Date:   Mon Jun 4 11:59:25 2012 +0100

 Improve error message for invalid package db file (#6133).

 Use `reads` instead of `read` to parse package configuration files,
 and
 report a meaningful error when the parsing fails.

  compiler/main/Packages.lhs |7 ++-
  1 files changed, 6 insertions(+), 1 deletions(-)
 }}}

-- 
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] #5936: Support for data families in generics

2012-06-04 Thread GHC
#5936: Support for data families in generics
-+--
Reporter:  reinerp   |   Owner:  dreixel 
Type:  feature request   |  Status:  patch   
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 Here's the relevant thread on the libraries list:
 [http://www.haskell.org/pipermail/libraries/2012-May/017815.html].
 Excerpts:

 Reiner: I have tried using GHC's new generic deriving
 [http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/generic-
 programming.html 2] to derive instances - this is almost possible, but is
 blocked by a GHC issue [http://hackage.haskell.org/trac/ghc/ticket/5936
 3]. IMHO generic deriving would be the best solution (once it works),
 because it works for product types as well as newtypes, and requires no
 extra GHC assistance or TH.


 Ben: This will be quite nice and it sounds like it should cover nearly all
 of the cases I'm interested in. I'm not terribly familiar with generics
 support so I'm not sure whether this is possible or not, but it would be
 great if there were a way to specify whether an SoA or AoS representation
 is derived. This way one could write nearly cache-optimal code while
 keeping the mechanics of data layout nicely contained.

-- 
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] #6140: segfault in OS X GHCi when dealing with infinite integers

2012-06-04 Thread GHC
#6140: segfault in OS X GHCi when dealing with infinite integers
---+
 Reporter:  olf|  Owner:   
 Type:  bug| Status:  new  
 Priority:  normal |  Component:  GHCi 
  Version:  6.10.4 |   Keywords:  segfault NaN Infinity
   Os:  MacOS X|   Architecture:  x86  
  Failure:  Runtime crash  |   Testcase:   
Blockedby: |   Blocking:   
  Related: |  
---+

Comment(by michalt):

 FYI: I've just tried this on OS X 10.7.4 with GHC 7.4.1 and everything
 works fine:
 {{{
 GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude> 1/0
 Infinity
 Prelude> negate (1/0)
 -Infinity
 Prelude>
 }}}

-- 
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] #6130: Weak pointer to MVar is finalized, even though MVar is still accessible

2012-06-04 Thread GHC
#6130: Weak pointer to MVar is finalized, even though MVar is still accessible
--+-
  Reporter:  jmillikin|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.6.1   
 Component:  Compiler |Version:  7.4.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by simonpj):

 Worth adding a regression test?

-- 
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] #6130: Weak pointer to MVar is finalized, even though MVar is still accessible

2012-06-04 Thread GHC
#6130: Weak pointer to MVar is finalized, even though MVar is still accessible
--+-
  Reporter:  jmillikin|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.6.1   
 Component:  Compiler |Version:  7.4.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * milestone:  => 7.6.1


-- 
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] #6130: Weak pointer to MVar is finalized, even though MVar is still accessible

2012-06-04 Thread GHC
#6130: Weak pointer to MVar is finalized, even though MVar is still accessible
--+-
  Reporter:  jmillikin|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.4.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

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


Comment:

 {{{
 commit b8df01cbaeb2203834a26838be18c9ca372c5881
 Author: Simon Marlow 
 Date:   Mon Jun 4 10:34:30 2012 +0100

 add mkWeakMVar; deprecate addMVarFinalizer (#6130)
 }}}

-- 
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] #6094: runInteractiveProcess not using new PATH

2012-06-04 Thread GHC
#6094: runInteractiveProcess not using new PATH
---+
  Reporter:  GregWeber |  Owner:  GregWeber   
  Type:  task  | Status:  closed  
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Compiler  |Version:  7.4.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * milestone:  => 7.6.1


-- 
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] #6094: runInteractiveProcess not using new PATH

2012-06-04 Thread GHC
#6094: runInteractiveProcess not using new PATH
---+
  Reporter:  GregWeber |  Owner:  GregWeber   
  Type:  task  | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.4.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

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


Comment:

 Done, in `libraries/process`:

 {{{
 commit 270e43a2138898967da904e3d61a6e2589cb7b1a
 Author: Simon Marlow 
 Date:   Mon Jun 4 10:41:18 2012 +0100

 Document the precise semantics of executable searching (see #6094)

 I had to do some research to figure out what we were actually doing
 here, and it appears we're using the platform semantics (ie. execvp()
 on Unix and CreateProcess() on Windows), so I've documented that.
 }}}

 and in `libraries/directory`:

 {{{
 commit 9b42efbdf4202bb50c6834f79f999fb2eee75f2e
 Author: Simon Marlow 
 Date:   Mon Jun 4 10:36:53 2012 +0100

 add findFile :: [FilePath] -> String -> IO (Maybe FilePath) (see
 #6094)

 Just an export of part of the implementation of findExecutable, which
 is useful for people wanting to do their own findExecutable using
 something other than the current PATH.
 }}}

-- 
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] #6141: ghc: panic! (the 'impossible' happened)

2012-06-04 Thread GHC
#6141: ghc: panic! (the 'impossible' happened)
---+
Reporter:  aSect   |Owner:   
Type:  bug |   Status:  closed   
Priority:  normal  |Component:  Compiler 
 Version:  7.4.1   |   Resolution:  invalid  
Keywords:  |   Os:  Linux
Architecture:  x86_64 (amd64)  |  Failure:  GHC rejects valid program
Testcase:  |Blockedby:   
Blocking:  |  Related:   
---+
Changes (by aSect):

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


-- 
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] #6141: ghc: panic! (the 'impossible' happened)

2012-06-04 Thread GHC
#6141: ghc: panic! (the 'impossible' happened)
---+
 Reporter:  aSect  |  Owner:
 Type:  bug| Status:  new   
 Priority:  normal |  Component:  Compiler  
  Version:  7.4.1  |   Keywords:
   Os:  Linux  |   Architecture:  x86_64 (amd64)
  Failure:  GHC rejects valid program  |   Testcase:
Blockedby: |   Blocking:
  Related: |  
---+
 i tried to load the following code in ghci:

 {-# OPTIONS_GHC -Wall -O2 #-}

 module Main where

 import Data.Map (Map)
 import qualified Data.Map as Map

 data Vertex a
= Vertex { vname :: a }
deriving (Show, Read, Eq)

 data Edge a
= Edge { xedge :: a
   , yedge :: a }
deriving (Show, Read, Eq)

 data Graph a
= Graph { vertexes  :: [Vertex a]
, edges :: [Edge a]
, adjacents :: Vertex a -> [Vertex a]
} deriving (show, Read, Eq)


 and then i got the following error:

 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.1 for x86_64-unknown-linux):
 nameModule show{tv a25N}

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-06-04 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by simonmar):

 I've been updating my Mac to the latest 10.8 and XCode, so hopefully I'll
 be able to answer that soon.

-- 
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] #6140: segfault in OS X GHCi when dealing with infinite integers

2012-06-04 Thread GHC
#6140: segfault in OS X GHCi when dealing with infinite integers
---+
 Reporter:  olf|  Owner:   
 Type:  bug| Status:  new  
 Priority:  normal |  Component:  GHCi 
  Version:  6.10.4 |   Keywords:  segfault NaN Infinity
   Os:  MacOS X|   Architecture:  x86  
  Failure:  Runtime crash  |   Testcase:   
Blockedby: |   Blocking:   
  Related: |  
---+
 GHCi happily reports the result of 1/0 to be "Infinity", but negating this
 value crashes.
 {{{
 GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Prelude> 1/0
 Infinity
 Prelude> negate (1/0)
 -Segmentation fault: 11
 }}}

 Bug occurs on OS X 10.7.4, ghc installed via MacPorts.
 This seems to be either an OS-specific issue, or maybe solved in later
 versions of ghc, since on a linux box it is not reproducible:

 {{{
 GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Prelude> 1/0
 Infinity
 Prelude> negate (1/0)
 -Infinity
 }}}

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-06-04 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by igloo):

 But the HP contains exactly the same GHC that didn't work, doesn't it?

 Isn't it more likely that the newer versions of OS X stuff fixed the
 linker?

-- 
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] #3160: No exception safety in Control.Concurrent.QSem QSemN and SampleVar

2012-06-04 Thread GHC
#3160: No exception safety in Control.Concurrent.QSem QSemN and SampleVar
--+-
  Reporter:  ChrisKuklewicz   |  Owner:  simonmar
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  7.6.1   
 Component:  libraries/base   |Version:  7.0.2   
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * owner:  => simonmar


Comment:

 Thanks. At the very least we should import the STM versions for 7.6.1.

-- 
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] #5741: openFile should fail if null bytes are in the argument

2012-06-04 Thread GHC
#5741: openFile should fail if null bytes are in the argument
--+-
  Reporter:  Veinor   |  Owner:  
  Type:  feature request  | Status:  closed  
  Priority:  high |  Milestone:  7.6.1   
 Component:  libraries/base   |Version:  7.2.1   
Resolution:  wontfix  |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

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


Comment:

 I'm inclined not to do anything here.  If you're allowing the user to
 supply a filename in a secure setting, you should do a lot more than just
 check for a `.cfg` extension, you should probably be extremely restrictive
 - e.g. the filename must be composed only of the characters
 `[A-Za-z0-9_.-]`.

-- 
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] #6130: Weak pointer to MVar is finalized, even though MVar is still accessible

2012-06-04 Thread GHC
#6130: Weak pointer to MVar is finalized, even though MVar is still accessible
-+--
Reporter:  jmillikin |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.4.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  => Unknown


Comment:

 I suspect this is just because the weak pointer is attached to the box,
 and not the primitive `MVar#` object underneath, and when optimisation is
 turned on GHC eliminates the box.  We should really have a `mkWeakMVar`
 operation, just like we have `mkWeakIORef` and `mkWeakThreadId`.

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-06-04 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by simonmar):

 That's good news.  However we don't know what made the problem go away, so
 it's possible it might re-emerge.

 Let's keep the ticket open until we can verify whether our 7.4.2
 distributions work on 10.8.

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