Re: [GHC] #2076: rational infinities don't compare correctly to each other

2012-12-04 Thread GHC
#2076: rational infinities don't compare correctly to each other
---+
  Reporter:  uhollerbach   |  Owner:  jeffrey 
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  _|_ 
 Component:  libraries/base|Version:  6.8.2   
Resolution:  wontfix   |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = wontfix


Comment:

 Lots of good discussion on this subject in #3676.  I think we concluded
 that `Rational` does not include infinity as a value.  Based on that, and
 the fact that `1%0` is actually `_|_`, I'm closing this ticket.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2076#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] #709: Fixup too large error with -fasm on PowerPC

2012-12-04 Thread GHC
#709: Fixup too large error with -fasm on PowerPC
--+-
  Reporter:  simonmar |  Owner:
  Type:  bug  | Status:  patch 
  Priority:  low  |  Milestone:  6.8.1 
 Component:  Compiler (NCG)   |Version:  7.7   
Resolution:   |   Keywords:
Os:  Unknown/Multiple |   Architecture:  powerpc   
   Failure:  Building GHC failed  | Difficulty:  Moderate (less than a day)
  Testcase:   |  Blockedby:
  Blocking:   |Related:
--+-

Comment(by simonmar):

 Hmm, this is an unpleasant bit of code :-)  hardcoded constants and
 guesses everywhere.

 Could we not use something better than a hardcoded 5 for the info table
 size?  We know the size of the info table for a continuation:
 `sizeof(StgRetInfoTable)`, and add to that the maximum offset due to
 alignment.

 You could also do better than `length blocks`: the actual number of info
 tables is available.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/709#comment:9
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] #7445: template-haskell : need a good error message instead of just an unexplained panic (was: template-haskell : the impossible happened)

2012-12-04 Thread GHC
#7445: template-haskell : need a good error message instead of just an 
unexplained
panic
---+
Reporter:  erikd   |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Template Haskell
 Version:  7.6.1   |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by erikd):

 Found the problem, for ```QuasiArith.hs``` I had:

 {{{
 module QuasiArith
 ( eval
 , expr
 ) where
 }}}

 If I change the module declaration to:

 {{{
 module QuasiArith where
 }}}

 it no longer panics and in fact even works and generates the correct
 result.

 I'm not sure what was causing it to fail. I tried exporting all top level
 functions and values in ```QuasiArith.hs``` and it still failed.

 Would in be sensible to disallow restricted exports for all files that
 import ```Language.Haskell.TH.Quote```?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7445#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] #7445: template-haskell : need a good error message instead of just an unexplained panic

2012-12-04 Thread GHC
#7445: template-haskell : need a good error message instead of just an 
unexplained
panic
---+
Reporter:  erikd   |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Template Haskell
 Version:  7.7 |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+
Changes (by erikd):

  * version:  7.6.1 = 7.7


Comment:

 Confirmed in GHC HEAD as well.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7445#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] #7462: New nofib benchmark for unpacked arrays and floating point arithmetic

2012-12-04 Thread GHC
#7462: New nofib benchmark for unpacked arrays and floating point arithmetic
--+-
Reporter:  tibbe  |   Owner:  
Type:  feature request|  Status:  patch   
Priority:  normal |   Milestone:  
   Component:  NoFib benchmark suite  | Version:  7.6.1   
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-
Changes (by simonmar):

  * difficulty:  = Unknown


Comment:

 Looks good.  Definitely a good idea to have more benchmarks.  Could you
 push it?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7462#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] #7445: template-haskell : need a good error message instead of just an unexplained panic

2012-12-04 Thread GHC
#7445: template-haskell : need a good error message instead of just an 
unexplained
panic
---+
Reporter:  erikd   |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Template Haskell
 Version:  7.7 |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by erikd):

 Hmm, this works:

 {{{
 module QuasiArith
 ( Expr (..)
 , BinOp (..)
 , eval
 , expr
 ) where
 }}}

 Problem seems to have been that type Expr and BinOp were not exported.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7445#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] #6017: Reading ./.ghci files raises security issues

2012-12-04 Thread GHC
#6017: Reading ./.ghci files raises security issues
-+--
Reporter:  nomeata   |   Owner:  pminten 
Type:  task  |  Status:  patch   
Priority:  high  |   Milestone:  7.8.1   
   Component:  GHCi  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Other   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 Let's not go overboard here. Even if we do a whitelist, someone will point
 out that we should be adding hashes of the .ghci file to the whitelist and
 failing if the hash doesn't match.

 If people think that this is really a security problem (and I'm not
 convinced it is, e.g. `gdb` reads `.gdbinit` unconditionally), then we can
 just switch the default to not read `.ghci` files in the current
 directory, and add a flag to enable it (`-ignore-dot-ghci` ignores all,
 but we want a way to just ignore the one in the current directory).  If
 you want to read a specific `.ghci` by default then there are lots of ways
 to do it: add some code to your `~/.ghci` to implement an explicit
 whitelist, or invoke ghci via a script or a shell alias.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6017#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] #7476: -ddump-minimal-imports confused if first line is an import

2012-12-04 Thread GHC
#7476: -ddump-minimal-imports confused if first line is an import
-+--
Reporter:  dag   |   Owner:  simonpj 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = simonpj
  * difficulty:  = Unknown


Comment:

 Very strange behaviour!  But the fix turned out to be easy.  I have a
 patch; need to validate before pushing.

 Thank you for reporting this

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7476#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] #7468: incorect waiting for packets on UDP connections.

2012-12-04 Thread GHC
#7468: incorect waiting for packets on UDP connections.
--+-
  Reporter:  ET   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  libraries/base   |Version:  7.4.1   
Resolution:  invalid  |   Keywords:  UDP packet loss.
Os:  Linux|   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = invalid


Comment:

 This is not a bug - Handles have buffers, so when you use `hWaitForInput`,
 the input is read into the buffer.  The `recv` function doesn't read from
 the `Handle`, so it doesn't see the data in the buffer.  The rule of thumb
 is that if you turn a socket into a `Handle`, you should use the `Handle`
 operations for reading and writing from then on.

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


[GHC] #7478: setSessionDynFlags does not always work

2012-12-04 Thread GHC
#7478: setSessionDynFlags does not always work
-+--
Reporter:  edsko |  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:  
-+--
 The attached test case runs GHC in a separate thread (with a single call
 to `runGhc` when the thread is started), waiting for compile requests on
 one channel and outputting done on another. Requests consist of a list
 of filenames to compile. These file names are added as targets and then
 `load LoadAddTargets` is called.

 On every request we also call `setSessionDynFlags` with a different
 `log_action`. On the first request the `log_action` is set to `dispatcher
 0` (defined in `forkGhc`), on the second request the `log_action` is set
 to `dispatcher 1`, and so on. This dispatcher just outputs the messages it
 receives from GHC, along with this integer; hence, all messages from the
 first request should include the integer 0, all messages from the second
 request should include the integer 1, and so on. However, when the program
 is run (in a directory containing all the specified source files), the
 output is

 {{{
 - 0 --
 (0,[1 of 2] Compiling B( B.hs, B.o ))
 (0,[2 of 2] Compiling Main ( A.hs, A.o ))
 - 1 --
 (0,[2 of 2] Compiling Main ( A.hs, A.o ))
 - 2 --
 (2,[1 of 1] Compiling Main ( C.hs, C.o ))
 (2,Linking A ...)
 }}}

 On the first request we ask Ghc to compile A.hs and B.hs; A.hs here
 depends on B.hs, which is compiled first, but A.hs contains an error and
 cannot be compiled. Then on the second request we ask GHC to compile A.hs
 and B.hs again; since B.hs is already compiled it only tries to compile
 A.hs, but this still fails. On the third request we ask Ghc to compile
 C.hs, an independent source file.

 Note that the integer listed for the second request is ''0'', not ''1''.
 For some reason the `setSessionDynFlags` does not seem to affect the
 recompilation of A.hs, even though when we compile C.hs in the third
 request, the output is ''2'', as expected.

 (This bug also occurs in GHC 7.4, but the API is slightly different so
 some minor modifications to to the code need to be made.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7478
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] #7478: setSessionDynFlags does not always work

2012-12-04 Thread GHC
#7478: setSessionDynFlags does not always work
-+--
Reporter:  edsko |  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:  
-+--

Comment(by edsko):

 Trac gave a database locked error when I uploaded B.hs; when I tried
 uploading it again, it added B.2.hs and then B.3.hs, even though it's
 not showing B.hs as being uploaded -- nor can I remove any of these
 files. Sigh. Please rename B.2.hs to B.hs before running the test.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7478#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] #7439: Include dynamic-by-default support in Cabal with GHC 7.6.2

2012-12-04 Thread GHC
#7439: Include dynamic-by-default support in Cabal with GHC 7.6.2
-+--
Reporter:  igloo |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  highest   |   Milestone:  7.6.2   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by trommler):

 * cc: ptrommler@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7439#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] #7478: setSessionDynFlags does not always work

2012-12-04 Thread GHC
#7478: setSessionDynFlags does not always work
-+--
Reporter:  edsko |  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:  
-+--

Comment(by edsko):

 Added a version of the the test that doesn't use concurrency/channels.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7478#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] #7479: ArrowChoice unit law in haddock seems to be wrong

2012-12-04 Thread GHC
#7479: ArrowChoice unit law in haddock seems to be wrong
--+-
Reporter:  pminten|  Owner:  
Type:  bug| Status:  new 
Priority:  normal |  Component:  libraries/base  
 Version:  7.7|   Keywords:  
  Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
 Failure:  Documentation bug  |  Blockedby:  
Blocking: |Related:  
--+-
 In the haddock documentation of !ArrowChoice there is an (unnamed) law:
 {{{left f  arr Left = arr Left  f}}}. In Ross Paterson's
 [http://www.soi.city.ac.uk/~ross/papers/fop.html Arrows and Computations]
 paper there is a similar law named the unit law for !ArrowChoice that goes
 {{{pure Left  left f = f  pure Left}}} (pure in that paper is
 arr in the base library).

 Reordering the unit law from the paper and replacing pure with arr the
 unit law from the paper is {{{f  arr Left = arr Left  left f}}}
 where the law from haddock is {{{left f  arr Left = arr Left 
 f}}}. The laws are similar but left is used in different places.

 The law from haddock appears to be invalid, there does not appear to be a
 way to create an arrow f in such a way that it works with both sides of
 the equation. This can be verified by typing the following lines in GHCi:

 {{{
 import Control.Arrow
 let foo f = left f  arr Left
 let bar f = arr Left  f
 let same :: a b c - a b c - (); same _ _ = ()
 \f - same (foo f) (bar f)
 }}}

 The last line gives a type error.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7479
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] #7479: ArrowChoice unit law in haddock seems to be wrong

2012-12-04 Thread GHC
#7479: ArrowChoice unit law in haddock seems to be wrong
--+-
Reporter:  pminten|  Owner:  
Type:  bug| Status:  merge   
Priority:  normal |  Component:  libraries/base  
 Version:  7.7|   Keywords:  
  Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
 Failure:  Documentation bug  |  Blockedby:  
Blocking: |Related:  
--+-
Changes (by ross):

  * status:  new = merge


Comment:

 Thanks for spotting this.  Fixed with
 {{{
 commit 96889ddccdcfc1fb852eeb3fdce7d4124f52376d
 Author: Ross Paterson r...@soi.city.ac.uk
 Date:   Tue Dec 4 19:32:40 2012 +

 fix #7479: ArrowChoice unit law in doc comment
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7479#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] #7162: RULES that never fire (automatically)

2012-12-04 Thread GHC
#7162: RULES that never fire (automatically)
---+
  Reporter:  andygill  |  Owner:  
  Type:  feature request   | Status:  new 
  Priority:  normal|  Milestone:  7.8.1   
 Component:  Compiler  |Version:  7.7 
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by afarmer):

 So while documenting this, I realized this patch makes an unintended
 change. Namely, the INLINE pragma uses the same parser rules for
 activation as the RULES pragma. So it is now possible to write:

 {-# INLINE [~] ... #-}
 and
 {-# NOINLINE [~] ... #-}

 Looking at RdrHsSyn.lhs, the first case (INLINE [~]) is equivalent to
 NOINLINE. Worryingly, I have yet to figure out how the second case
 (NOINLINE [~]) behaves.

 So as I see it, there are two possible solutions.

 1. I submit a new patch to the parser that separates the activation
 parsing for RULES and INLINE so RULES [~] is possible but INLINE [~] is
 not.

 2. I figure out what NOINLINE [~] means and document that.

 Opinions? I'm inclined towards option 1, as I think it'll be less
 confusing for the user.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7162#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] #7320: GHC crashes when building on 32-bit Linux in a Linode

2012-12-04 Thread GHC
#7320: GHC crashes when building on 32-bit Linux in a Linode
---+
Reporter:  benl|   Owner:  simonmar  
Type:  bug |  Status:  new   
Priority:  high|   Milestone:  7.6.2 
   Component:  Runtime System  | Version:  7.6.1 
Keywords:  |  Os:  Linux 
Architecture:  x86 | Failure:  Compile-time crash
  Difficulty:  Unknown |Testcase:
   Blockedby:  |Blocking:
 Related:  |  
---+

Comment(by Irene):

 I reproduce this on my linode, and am willing to help debug.  It
 reproduces essentially 100% for me when I try to build ghc 7.6.1 from
 source, always faililng at different spots and usually with a segfault.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7320#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] #7462: New nofib benchmark for unpacked arrays and floating point arithmetic

2012-12-04 Thread GHC
#7462: New nofib benchmark for unpacked arrays and floating point arithmetic
+---
  Reporter:  tibbe  |  Owner:  
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  NoFib benchmark suite  |Version:  7.6.1   
Resolution:  fixed  |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by tibbe):

  * status:  patch = closed
  * resolution:  = fixed


Comment:

 Merged as 14bccff2c547c0e06fe8f98607b9cf18890ef051.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7462#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] #7480: Proposal: Add Functor instances for ArgOrder, OptDescr and ArgDescr

2012-12-04 Thread GHC
#7480: Proposal: Add Functor instances for ArgOrder, OptDescr and ArgDescr
-+--
Reporter:  basvandijk|  Owner:  
Type:  feature request   | Status:  new 
Priority:  normal|  Component:  libraries/base  
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 The attached patch adds Functor instances for the types in
 [http://hackage.haskell.org/packages/archive/base/latest/doc/html/System-
 Console-GetOpt.html System.Console.GetOpt].

 Note that the `test-framework` package also
 [http://hackage.haskell.org/packages/archive/test-
 framework/0.6.1/doc/html/src/Test-Framework-Runners-Console.html defines]
 these instances.

 There were no -1s on the
 [http://www.haskell.org/pipermail/libraries/2012-November/018823.html
 thread] on the libraries list.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7480
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] #709: Fixup too large error with -fasm on PowerPC

2012-12-04 Thread GHC
#709: Fixup too large error with -fasm on PowerPC
--+-
  Reporter:  simonmar |  Owner:
  Type:  bug  | Status:  patch 
  Priority:  low  |  Milestone:  6.8.1 
 Component:  Compiler (NCG)   |Version:  7.7   
Resolution:   |   Keywords:
Os:  Unknown/Multiple |   Architecture:  powerpc   
   Failure:  Building GHC failed  | Difficulty:  Moderate (less than a day)
  Testcase:   |  Blockedby:
  Blocking:   |Related:
--+-

Comment(by PHO):

 Replying to [comment:9 simonmar]:
  Hmm, this is an unpleasant bit of code :-)  hardcoded constants and
 guesses everywhere.

 It is unpleasant indeed. My patch makes a dirty hack even dirtier :(


  Could we not use something better than a hardcoded 5 for the info
 table size?  We know the size of the info table for a continuation:
 `sizeof(StgRetInfoTable)`, and add to that the maximum offset due to
 alignment.

 The size of `StgRetInfoTable` varies depending on the way (e.g. -prof)
 so we can't simply grab it from the C compiler. I think it's easy to
 calculate the size of each tables represented as `CmmStatics`.


  You could also do better than `length blocks`: the actual number of info
 tables is available.

 Right, but since info tables are scattered around a proc, I couldn't
 simply replace {{{length blocks}}} with the actual number of tables.

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