Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-01-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * milestone:  7.6.1 = 7.4.2


Comment:

 We don't have to wait until 7.6.1 to fix this, if the fix can be made with
 minimal disruption.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5688#comment:35
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] #5764: Double addition error

2012-01-12 Thread GHC
#5764: Double addition error
-+--
 Reporter:  jimstutt |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.2.2|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  x86 
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 ghci0.1+0.2
 ghci3.004

 ghc produces the same result with:

 foldl (+) [0.1,0.2]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5764
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] #5764: Double addition error

2012-01-12 Thread GHC
#5764: Double addition error
-+--
 Reporter:  jimstutt |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.2.2|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  x86 
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by jimstutt):

 Sorry foldl (+) 0 [0.1,0.2]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5764#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] #5764: Double addition error

2012-01-12 Thread GHC
#5764: Double addition error
-+--
Reporter:  jimstutt  |Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Component:  Compiler   
 Version:  7.2.2 |   Resolution:  invalid
Keywords:|   Os:  Unknown/Multiple   
Architecture:  x86   |  Failure:  Incorrect result at runtime
Testcase:|Blockedby: 
Blocking:|  Related: 
-+--
Changes (by ross):

  * status:  new = closed
  * resolution:  = invalid


Comment:

 It's an artifact of fixed-precision floating point not being able to
 represent decimal fractions exactly; you get the same from C:
 {{{
 #include stdio.h

 int main() {
 printf(%.17f\n, 0.1+0.2);
 return 0;
 }
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5764#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] #5765: ghc-cabal build failure with nonsense error message

2012-01-12 Thread GHC
#5765: ghc-cabal build failure with nonsense error message
-+--
 Reporter:  jimstutt |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.2.2|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  x86 
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 Trying to install a second user instance of ghc-7.2.2 from
 ghc-7.2.2-src.tar.bz2 with config.mk.in edited to integer-simple and
 $GHC_PACKAGE_PATH set gives the following message:

 Configuring Cabal-1.12.0... ghc-cabal: At least the following
 dependencies are missing
 base =4  3  =2  5
 filepath  =1   1.3
 unix = 2.0  2.6
 make[1]: ** [libraries/Cabal/cabal/dist-boot/package-data.mk] Error 1
 make: ***[all] Error 1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5765
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] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-01-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by iustin):

 Replying to [comment:34 igloo]:
  Replying to [comment:33 iustin]:
   Replying to [comment:31 igloo]:
This isn't a regression, so let's punt it to 7.6.
  
   It's not a regression, but IMHO it's a security bug.
 
  I don't think a DoS is as bad a problem as the phrase security bug
 implies.

 True. Can it be confirmed that a most this does is a crash of the runtime,
 with no other bad behaviours?

 
   As such, it should be fixed even in lower versions, not only in a
 future one!
 
  We're not set up to be able to make releases on old branches.

 As I wrote in a previous comment, you don't need to make a full release,
 but for long-term distributions it would be very helpful if you release an
 official patch against older versions, that can be applied.

   I might overreact (sorry) but dragging the feet on such issues make it
 hard to promote the use of Haskell…
 
  Well, pragmatically speaking, currently we're past the feature freeze
 and into the RC phase (so ideally wouldn't be changing the definition of
 `Read Integer` etc), the release is already long overdue, and we don't
 have a good fix yet.

 Again, I don't propose to delay the release. What I'm interested in is to
 know for production environments that still run an older GHC release (6.12
 as that is in current Debian stable and Ubuntu LTS and 7.0/7.2), they can
 apply a blessed patch to their build systems in order to safeguard
 against this (once a good solution is found; I expect the fix to probably
 apply without issues to older versions too). That's all - the update of
 Milestone to 7.6 worried me that all older versions are left out in the
 cold.

 thanks again,
 iustin

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5688#comment:36
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] #5567: LLVM: Improve alias analysis / performance

2012-01-12 Thread GHC
#5567: LLVM: Improve alias analysis / performance
-+--
Reporter:  dterei|   Owner:  dterei 
Type:  task  |  Status:  new
Priority:  normal|   Milestone:  7.6.1  
   Component:  Compiler (LLVM)   | Version: 
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:|Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by dterei):

 OK, tried this benchmark:

 {{{
 module Main(main) where

 import Data.Array.Base
 import Data.Array.IO
 import Data.Array.MArray

 main :: IO ()
 main = do
 arr - newArray_ (0, 200)
 go arr 2 0 100

 go :: IOUArray Int Int - Int - Int - Int - IO ()
 go arr stride x y | x  y = do unsafeWrite arr (x * stride) 1337
go arr stride (x + 1) y
  | otherwise = return ()
 }}}

 And not working as I seem to be adding the TBAA info wrong. I think we
 need an unknown type (for pointers loaded from RX registers) that doesn't
 alias Sp.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5567#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] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-01-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 A fix should be easy. If the `Rat` constructor is not changed or removed
 it should be at least filled with the fractionals that are given without
 e (to allow some user code to go through, although with reduced
 functionality).

 The `Exp` constructor should store the fractional part as `Rational`
 rather than shifting it to an `Integer` an decreasing the exponent.

 A combination of the `Rat` and `Exp` constructores is then essential
 Daniels suggestion `| RatExp Rational (Maybe Integer)`.

 An advantage of removing `Rat` would be to better detect code that uses
 it.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5688#comment:37
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] #4041: Zwierzęta świata i rekord księgi (was: possible misbehaviour of hGet/hGetBuf)

2012-01-12 Thread GHC
#4041: Zwierzęta świata i rekord księgi
--+-
  Reporter:  duncan   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  libraries/base   |Version:  6.12.1  
Resolution:  fixed|   Keywords:  
Os:  MacOS X  |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by karina26):

 Dumasz nad tym jakie są granice możliwości ludzkich? Z pewnością
 interesują Cię [http://rekordyguinessa.pl/rekordy-guinessa-zwierzat/
 zwierzęta świata]. Słyszałeś o najpopularniejszej na całym świecie księdze
 rekordów i chcesz sprawdzić przykładowe [http://rekordyguinessa.pl/
 rekord]. Pragniemy gorąco zaprosić Cię na naszą witrynę WWW na której
 odnajdziesz informacje związane z [http://rekordyguinessa.pl/ksiega-
 rekordow-guinessa/ księgi], a więc biciem rekordów Guinnessa! Sprawdź
 nasze rekordy Guinnessa.

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


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-01-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 Another advantage of removing `Rat` is, that code duplication to treat the
 `Rational` within `Rat` and `Exp`(i.e. the conversion to `Double`) is
 avoided.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5688#comment:38
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] #5764: Double addition error

2012-01-12 Thread GHC
#5764: Double addition error
--+-
  Reporter:  jimstutt |  Owner: 
  Type:  bug  | Status:  closed 
  Priority:  normal   |  Milestone: 
 Component:  Compiler |Version:  7.2.2  
Resolution:  invalid  |   Keywords: 
Os:  Unknown/Multiple |   Architecture:  x86
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
  Testcase:   |  Blockedby: 
  Blocking:   |Related: 
--+-
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 Well, if `0.1+0.2` really gave result `3.04`, as reported, THAT
 would be a bug.  But it doesn't. It gives `0.34`. Wich as Ross
 says is fine.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5764#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] #5738: System.Posix.Temp mkstemp bugs and addition of mkdtem

2012-01-12 Thread GHC
#5738: System.Posix.Temp mkstemp bugs and addition of mkdtem
-+--
  Reporter:  deian   |  Owner:  dterei
  Type:  bug | Status:  closed
  Priority:  normal  |  Milestone:
 Component:  libraries/unix  |Version:  7.2.1 
Resolution:  fixed   |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  Compile-time crash  | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--

Comment(by simonmar):

 In the distant past it compiled on Cygwin, when we had a Cygwin build.  I
 have no objection to removing the Windows parts now.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5738#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] #5624: Delay Errors Until Runtime

2012-01-12 Thread GHC
#5624: Delay Errors Until Runtime
-+--
Reporter:  atnnn |   Owner:  atnnn   
Type:  feature request   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.3 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:|Testcase:  
   Blockedby:|Blocking:  
-+--

Comment(by simonpj@…):

 commit 5508ada4b1d90ee54d92f69bbff7f66b3e8eceef
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Thu Jan 12 15:10:54 2012 +

 Implememt -fdefer-type-errors (Trac #5624)

 This patch implements the idea of deferring (most) type errors to
 runtime, instead emitting only a warning at compile time.  The
 basic idea is very simple:

  * The on-the-fly unifier in TcUnify never fails; instead if it
gets stuck it emits a constraint.

  * The constraint solver tries to solve the constraints (and is
entirely unchanged, hooray).

  * The remaining, unsolved constraints (if any) are passed to
TcErrors.reportUnsolved.  With -fdefer-type-errors, instead of
emitting an error message, TcErrors emits a warning, AND emits
a binding for the constraint witness, binding it
to (error the error message), via the new form of evidence
TcEvidence.EvDelayedError.  So, when the program is run,
when (and only when) that witness is needed, the program will
crash with the exact same error message that would have been
given at compile time.

 Simple really.  But, needless to say, the exercise forced me
 into some major refactoring.

  * TcErrors is almost entirely rewritten

  * EvVarX and WantedEvVar have gone away entirely

  * ErrUtils is changed a bit:
  * New Severity field in ErrMsg
  * Renamed the type Message to MsgDoc (this change
touches a lot of files trivially)

  * One minor change is that in the constraint solver we try
NOT to combine insoluble constraints, like Int~Bool, else
all such type errors get combined together and result in
only one error message!

  * I moved some definitions from TcSMonad to TcRnTypes,
where they seem to belong more

  compiler/coreSyn/CoreLint.lhs  |   76 ++--
  compiler/deSugar/DsBinds.lhs   |7 +-
  compiler/deSugar/DsMonad.lhs   |5 +-
  compiler/ghci/Linker.lhs   |4 +-
  compiler/hsSyn/Convert.lhs |   20 +-
  compiler/iface/LoadIface.lhs   |   10 +-
  compiler/iface/MkIface.lhs |2 +-
  compiler/iface/TcIface.lhs |2 +-
  compiler/main/CmdLineParser.hs |3 +-
  compiler/main/DynFlags.hs  |   16 +-
  compiler/main/ErrUtils.lhs |  157 
  compiler/main/ErrUtils.lhs-boot|4 +-
  compiler/main/HeaderInfo.hs|2 +-
  compiler/main/HscMain.hs   |8 +-
  compiler/main/HscTypes.lhs |4 +-
  compiler/main/Packages.lhs |8 +-
  compiler/parser/Lexer.x|6 +-
  compiler/rename/RnEnv.lhs  |4 +-
  compiler/rename/RnNames.lhs|6 +-
  compiler/simplCore/CoreMonad.lhs   |2 +-
  compiler/stgSyn/StgLint.lhs|   40 +-
  compiler/typecheck/Inst.lhs|   60 +--
  compiler/typecheck/TcBinds.lhs |4 +-
  compiler/typecheck/TcCanonical.lhs |  106 +++--
  compiler/typecheck/TcDeriv.lhs |   10 +-
  compiler/typecheck/TcErrors.lhs|  876
 +---
  compiler/typecheck/TcEvidence.lhs  |   19 +-
  compiler/typecheck/TcExpr.lhs  |2 +-
  compiler/typecheck/TcForeign.lhs   |4 +-
  compiler/typecheck/TcHsSyn.lhs |3 +
  compiler/typecheck/TcInteract.lhs  |   77 ++--
  compiler/typecheck/TcMType.lhs |   13 +-
  compiler/typecheck/TcMatches.lhs   |   18 +
  compiler/typecheck/TcRnDriver.lhs  |2 +-
  compiler/typecheck/TcRnMonad.lhs   |  149 ---
  compiler/typecheck/TcRnTypes.lhs   |  202 +
  compiler/typecheck/TcSMonad.lhs|   84 +
  compiler/typecheck/TcSimplify.lhs  |  140 --
  compiler/typecheck/TcSplice.lhs|8 +-
  compiler/typecheck/TcType.lhs  |   75 +++-
  compiler/typecheck/TcUnify.lhs |  162 +++-
  compiler/types/InstEnv.lhs |2 +-
  compiler/types/Unify.lhs   |6 +-
  docs/users_guide/flags.xml |   32 +-
  docs/users_guide/using.xml |   26 ++
  45 files changed, 1340 insertions(+), 1126 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5624#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell 

Re: [GHC] #5535: Performance regression vs. 7.2.1

2012-01-12 Thread GHC
#5535: Performance regression vs. 7.2.1
-+--
Reporter:  simonmar  |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Compiler  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by igloo):

  * difficulty:  = Unknown


Comment:

 OK, I think the essence of the problem is here:
 {{{
 {-# LANGUAGE MagicHash, UnboxedTuples #-}

 module Q (whenDiverge) where

 import GHC.Base
 import GHC.Integer

 whenDiverge :: Int - Int - Double - Bool
 whenDiverge limit radius d
   = walkIt (replicate limit d)
   where
  walkIt []  = True
  walkIt (x : _)
 | diverge x radius  = True
 | otherwise = False

 diverge :: Double - Int - Bool
 diverge d radius = exponentDouble d  radius

 exponentDouble :: Double - Int
 exponentDouble x = case decodeDouble x of
(m,n) - if m == (0 :: Integer)
 then (0 :: Int)
 else n + floatDigits x

 decodeDouble :: Double - (Integer, Int)
 decodeDouble (D# x#) = case decodeDoubleInteger x# of
(# i, j #) - (i, I# j)
 }}}

 When compiled with 7.2.1 `-O2`, the two top-level functions (`whenDiverge`
 and its wrapper) have `Caf=NoCafRefs`. When compiled with HEAD, they
 don't. It looks like the problem is the `(0 :: Integer)` literal, which
 under the hood uses `GHC.Integer.Type.mkInteger`, which calls
 `negateInteger`, which has a CAF for the (minBound :: Int) case.

 So I changed it not to use a CAF:
 {{{
 -negateInteger (S# INT_MINBOUND) = NEG_INT_MINBOUND
 +negateInteger i@(S# INT_MINBOUND) = negateInteger (toBig i)
 }}}
 and now `negateInteger` and `mkInteger` have `HasNoCafRefs` in the
 `GHC.Integer.Type` interface file, but `whenDiverge` still doesn't have
 it.

 Simon, any idea what's going wrong please?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5535#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] #5535: Performance regression vs. 7.2.1

2012-01-12 Thread GHC
#5535: Performance regression vs. 7.2.1
-+--
Reporter:  simonmar  |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Compiler  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by igloo):

 Oh, I was missing the obvious: The integer constant itself is now being
 turned into a CAF.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5535#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] #5535: Performance regression vs. 7.2.1

2012-01-12 Thread GHC
#5535: Performance regression vs. 7.2.1
-+--
Reporter:  simonmar  |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Compiler  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 So why does that matter (for execution time)?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5535#comment:4
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] #5658: Strict bindings are wrongly floated out of case alternatives.

2012-01-12 Thread GHC
#5658: Strict bindings are wrongly floated out of case alternatives.
-+--
Reporter:  benl  |   Owner:  benl
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.4.1   
   Component:  Compiler  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Runtime crash   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj@…):

 commit 3beb1a831b37f616b5e8092def2e51cd9825735f
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Thu Jan 12 17:17:22 2012 +

 Fix Trac #5658: strict bindings not floated in

 Two changes here

 * The main change here is to enhance the FloatIn pass so that it can
   float case-bindings inwards.  In particular the case bindings for
   array indexing.

 * Also change the code in Simplify, to allow a case on array
   indexing (ie can_fail is true) to be discarded altogether if its
   results are unused.

 Lots of new comments in PrimOp about can_fail and has_side_effects

 Some refactoring to share the FloatBind data structure between
 FloatIn and FloatOut

  compiler/coreSyn/CorePrep.lhs   |2 +-
  compiler/coreSyn/CoreUtils.lhs  |   55 +++--
  compiler/coreSyn/MkCore.lhs |   22 +
  compiler/prelude/PrimOp.lhs |  163
 ++-
  compiler/simplCore/FloatIn.lhs  |  123 +++---
  compiler/simplCore/FloatOut.lhs |   20 +
  compiler/simplCore/SimplEnv.lhs |1 +
  compiler/simplCore/Simplify.lhs |   10 ++-
  8 files changed, 237 insertions(+), 159 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5658#comment:18
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] #3207: readMutVar# is inlined/duplicated

2012-01-12 Thread GHC
#3207: readMutVar# is inlined/duplicated
--+-
  Reporter:  simonmar |  Owner:  igloo   
  Type:  merge| Status:  closed  
  Priority:  normal   |  Milestone:  6.10 branch 
 Component:  Compiler |Version:  6.10.2  
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown | Difficulty:  Unknown 
  Testcase:  codeGen/should_run/3207  |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonpj):

  * testcase:  = codeGen/should_run/3207
  * failure:  = None/Unknown


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3207#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] #5658: Strict bindings are wrongly floated out of case alternatives.

2012-01-12 Thread GHC
#5658: Strict bindings are wrongly floated out of case alternatives.
-+--
Reporter:  benl  |   Owner:  benl   
Type:  bug   |  Status:  merge  
Priority:  high  |   Milestone:  7.4.1  
   Component:  Compiler  | Version:  7.2.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime crash  
  Difficulty:  Unknown   |Testcase:  simplCore/should_compile/T5658b
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * testcase:  = simplCore/should_compile/T5658b


Comment:

 Test `T5658b` is a simple test of Roman's program.

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


Re: [GHC] #5535: Performance regression vs. 7.2.1

2012-01-12 Thread GHC
#5535: Performance regression vs. 7.2.1
-+--
Reporter:  simonmar  |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Compiler  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by igloo):

 Hmm, looks like it was a red herring.

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


Re: [GHC] #5535: Performance regression vs. 7.2.1

2012-01-12 Thread GHC
#5535: Performance regression vs. 7.2.1
---+
  Reporter:  simonmar  |  Owner:  igloo   
  Type:  bug   | Status:  closed  
  Priority:  highest   |  Milestone:  7.4.1   
 Component:  Compiler  |Version:  7.2.1   
Resolution:  wontfix   |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by igloo):

  * status:  new = closed
  * resolution:  = wontfix


Comment:

 OK, in the end I don't think there's anything bad actually going wrong
 here. ticky shows that we now call a number of `integer-gmp` functions a
 lot, but that's to be expected as we no longer inline them (and we can't
 inline them, because that can cause code size explosion).

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


[GHC] #5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode

2012-01-12 Thread GHC
#5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode
--+-
 Reporter:  basvandijk|  Owner:   
 Type:  bug   | Status:  new  
 Priority:  normal|  Component:  libraries/process
  Version:  7.2.2 |   Keywords:   
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple 
  Failure:  None/Unknown  |   Testcase:   
Blockedby:|   Blocking:   
  Related:|  
--+-
 As [http://www.haskell.org/pipermail/libraries/2012-January/017406.html
 explained] on the libraries list, I fixed two asynchronous exception bugs
 in `readProcess` and
 `readProcessWithExitCode`:

 1) If an asynchronous exception was thrown to the thread executing
 `readProcess`/`readProcessWithExitCode` somewhere after `createProcess`
 was executed, the standard handles would not be closed anymore resulting
 in a handle leak so to speak.

 This is fixed by catching exceptions in the IO processing code and
 closing the standard handles when an exception occurs. Additionally, I
 also terminate the process and wait for its termination. Does the
 latter make sense?

 2) If an asynchronous exception was thrown to the stdout/stderr-read-
 thread it did not execute the `putMVar` anymore resulting in a dead-lock
 when `takeMVar` was executed.

 This is fixed by properly catching exception in the read-thread and
 propagating them to the parent thread which will then handle them as
 described above.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5766
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] #5467: Template Haskell: support for Haddock comments

2012-01-12 Thread GHC
#5467: Template Haskell: support for Haddock comments
-+--
Reporter:  reinerp   |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.6.1   
   Component:  Template Haskell  | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:|Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by SimonHengel):

 * cc: sol@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5467#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] #5757: zero unexpected failures on all tier 1 platforms

2012-01-12 Thread GHC
#5757: zero unexpected failures on all tier 1 platforms
-+--
Reporter:  simonmar  |   Owner:  
Type:  task  |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Test Suite| Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by dterei):

 On Linux x64 under 'optasm' and 'optllvm' I currently get the following
 failures:
 {{{
 OVERALL SUMMARY for test run started at Thu Jan 12 15:33:24 PST 2012
 3195 total tests, which gave rise to
15839 test cases, of which
0 caused framework failures
14360 were skipped

 1442 expected passes
   19 had missing libraries
   17 expected failures
0 unexpected passes
1 unexpected failures

 Unexpected failures:
lib/Time  T5430 [bad stdout] (optasm)
 }}}

 where 'T5430' fails with:
 {{{
 = T5430(optasm) 1895 of 3195 [0, 0, 0]
 cd ./lib/Time  '/home/davidt/Ghc/head-next/inplace/bin/ghc-stage2'
 -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-
 conf -rtsopts  -fno-ghci-history -o T5430 T5430.hs -O -fasm
 T5430.comp.stderr 21
 cd ./lib/Time  ./T5430/dev/null T5430.run.stdout
 2T5430.run.stderr
 Actual stdout output differs from expected:
 --- ./lib/Time/T5430.stdout   2011-11-16 15:50:57.665397562 -0800
 +++ ./lib/Time/T5430.run.stdout  2012-01-12 15:37:50.188034971 -0800
 @@ -1 +1 @@
 -001
 +365
 *** unexpected failure for T5430(optasm)
 }}}

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


[GHC] #5767: Integer inefficiencies

2012-01-12 Thread GHC
#5767: Integer inefficiencies
-+--
 Reporter:  rl   |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.5  |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 Here is a small program:

 {{{
 module T where
 foo :: RealFrac a = a - a - Int
 {-# INLINE [0] foo #-}
 foo x y = truncate $ (y-x)+2

 module U where
 import T
 bar :: Int - Int
 bar x = foo 1 50 + x
 }}}

 GHC 7.2.2 generates this optimal code:

 {{{
 bar = \ (x_abs :: Int) - case x_abs of _ { I# y_auX - I# (+# 51 y_auX) }
 }}}

 Whereas the current HEAD generates this:

 {{{
 bar2 :: Integer
 bar2 = __integer 2

 bar1 :: Int
 bar1 =
   case doubleFromInteger bar2
   of wild_arl { __DEFAULT - I# (double2Int# (+## 49.0 wild_arl)) }

 bar :: Int - Int
 bar = \ (x_a9S :: Int) - plusInt bar1 x_a9S
 }}}

 If I remove the INLINE pragma from `foo`, the HEAD generates this:

 {{{
 bar1 :: Int
 bar1 =
   case doubleFromInteger foo1
   of wild_asr { __DEFAULT -
   case GHC.Float.$w$cproperFraction
  @ Int GHC.Real.$fIntegralInt (+## 49.0 wild_asr)
   of _ { (# ww1_as1, _ #) -
   ww1_as1
   }
   }

 bar :: Int - Int
 bar = \ (x_a9W :: Int) - plusInt bar1 x_a9W
 }}}

 Interestingly, without the INLINE pragma 7.2.2 doesn't fare much better.

 I've also seen this bit in the generated code with the HEAD but not with
 7.2.2:

 {{{
 case integerToInt (smallInteger a_s2jL) of wild_a1dA { __DEFAULT - f
 wild_a1dA }
 }}}

 I couldn't boil it down to a small test case yet but it leads to a
 significant performance regression in at least one `vector` benchmark. I
 suppose fixing this is only a matter of adding an
 `integerToInt/smallInteger` rule.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5767
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] #5757: zero unexpected failures on all tier 1 platforms

2012-01-12 Thread GHC
#5757: zero unexpected failures on all tier 1 platforms
-+--
Reporter:  simonmar  |   Owner:  
Type:  task  |  Status:  new 
Priority:  highest   |   Milestone:  7.4.1   
   Component:  Test Suite| Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by dterei):

 OK I fixed T5430. Output on Linux x64 is good for me (under optasm,
 optllvm anyway).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5757#comment:4
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] #5567: LLVM: Improve alias analysis / performance

2012-01-12 Thread GHC
#5567: LLVM: Improve alias analysis / performance
-+--
Reporter:  dterei|   Owner:  dterei 
Type:  task  |  Status:  new
Priority:  normal|   Milestone:  7.6.1  
   Component:  Compiler (LLVM)   | Version: 
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:|Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by dterei):

 Pushed an improvement: e10589a505b44f4f0394500c6a0d2db5baa7f3f4

 This gets the good code generated for the above benchmark improving
 performance by around 20%! Also added control to enable or disable if TBAA
 is used with: ba52053b95ccb417ca7ce08e85a45e49b5f49b0a

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