[GHC] #2730: Quasiquote or TH linking may need HPC flag

2008-10-30 Thread GHC
#2730: Quasiquote or TH linking may need HPC flag
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  6.10.1  
   Component:  Compiler  | Version:  6.8.3   
Severity:  normal|Keywords:  
  Difficulty:  Unknown   |Testcase:  
Architecture:  Unknown/Multiple  |  Os:  Unknown/Multiple
-+--
 Test `quasiquotation/qq005` fails in the `hpc` way:
 {{{
 '/64playpen/simonpj/builds/HEAD-1/ghc/stage2-inplace/ghc' -fforce-recomp
 -dcore-lint -dcmm-lint -Dx86_64_unknown_linux  -dno-debug-output -c -o
 qq005 Main.hs -O -fhpc
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Loading package syb ... linking ... done.
 Loading package array-0.2.0.0 ... linking ... done.
 Loading package packedstring-0.1.0.1 ... linking ... done.
 Loading package containers-0.2.0.0 ... linking ... done.
 Loading package pretty-1.0.1.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Loading package parsec-2.1.0.1 ... linking ... done.
 ghc: ./Expr.o: unknown symbol `hs_hpc_module'
 }}}
 I believe the reason is this:
  * `Expr.hs` contains a quasiquote parser
  * This parser is invoked in `Main.hs`
  * But `Expr.hs` is compiled with `-fhpc` and contains a reference to the
 RTS function `hs_hpc_module`
  * When doing dynamic linking of `Expr.o` (to run the quasiquote parser)
 the linker can't find `hs_hpc_module`.  (Even though `Main.hs` is also
 compiled with `-fhpc`.

 The same thing happens with Template Haskell. (Try running the `th` tests
 with the `hpc` way.  Not all tests fail, but some do, with the same
 error.)

 I'm no expert on the dynamic linking part. Is `hs_hpc_module` (defined in
 `rts/Hpc.c`) always part of the RTS?  Does it need to be added to a list I
 vaguely recall, of externally linkable symbols (perhaps `RTS_SYMBOLS` in
 `rts/Linker.c`) [PS: some comments explaining these lists would be v
 useful]?  Or what?

 I'll milestone this for 6.10.1, because it does seem a bug that TH and HPC
 don't mix; but it should probably not hold up the release.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2730
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] #2670: Record selectors behaving badly wrt optimisation

2008-10-30 Thread GHC
#2670: Record selectors behaving badly wrt optimisation
--+-
 Reporter:  simonmar  |  Owner:  simonpj 
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  6.10.2  
Component:  Compiler  |Version:  6.8.3   
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by simonpj):

  * summary:  Performance regression = Record selectors behaving badly wrt
  optimisation

Comment:

 Just adding a couple more notes:
   * When field packing/unpacking is involved, if the selector is not
 inlined bodily (perhaps it is big), then we'd like strictness and CPR
 info; and indeed a worker/wrapper split.  Again that argues for making
 them ordinary functions.

   * Injecting the selectors into the CoreBinds early (ie at the start of
 the optimisation passes) doesn't help much.  Since they are `GlobalIds`,
 any uses of the selectors still don't see the bindings, instead using
 the unfolding put inside the selector by `MkId`.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2670#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] #2731: Avoid unnecessary evaluation when unpacking constructors

2008-10-30 Thread GHC
#2731: Avoid unnecessary evaluation when unpacking constructors
-+--
Reporter:  simonpj   |   Owner:  
Type:  run-time performance bug  |  Status:  new 
Priority:  normal|   Milestone:  6.12 branch 
   Component:  Compiler  | Version:  6.8.3   
Severity:  normal|Keywords:  
  Difficulty:  Unknown   |Testcase:  
Architecture:  Unknown/Multiple  |  Os:  Unknown/Multiple
-+--
 Consider
 {{{
 data T a = MkT !a

 foo :: T (a,b) - a
 foo (MkT (x,y)) = x
 }}}
 GHC will extract the first component of the `MkT`, ''evaluate it'', and
 then extract the first component of the pair.  The evaluation step isn't
 needed, since the component is known to be already-evaluated.  `UNPACK`
 directives won't work here, because the component is polymorphic.

 In the email thread, Tyson posted an example where this extra eval made a
 significant difference to his inner loop:
 [http://www.haskell.org/pipermail/glasgow-haskell-
 users/2008-October/015796.html]

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2731
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] #2722: loop when compiling with -O option with ghc-6.10.0.20081019

2008-10-30 Thread GHC
#2722: loop when compiling with -O option with ghc-6.10.0.20081019
---+
 Reporter:  uwe|  Owner: 
 Type:  bug| Status:  new
 Priority:  high   |  Milestone:  6.10.1 
Component:  Compiler   |Version:  6.10.1 
 Severity:  normal | Resolution: 
 Keywords:  Optimization Loop  | Difficulty:  Unknown
 Testcase: |   Architecture:  x86
   Os:  Linux  |  
---+
Comment (by simonpj):

 That's a big program!  Can you say why you suspect `id` and `(.)`, and/or
 `Control.Arrow.*`?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2722#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] #2674: ghc panic TcPat.checkArgs

2008-10-30 Thread GHC
#2674: ghc panic TcPat.checkArgs
--+-
 Reporter:  rwbarton  |  Owner:  igloo   
 Type:  merge | Status:  new 
 Priority:  normal|  Milestone:  6.10.1  
Component:  Template Haskell  |Version:  6.8.2   
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:  th/T2674  |   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by simonpj):

  * testcase:  = th/T2674
  * owner:  = igloo
  * type:  bug = merge

Comment:

 Thanks for the report. Fixed by
 {{{
 Thu Oct 30 09:45:28 GMT 2008  [EMAIL PROTECTED]
   * Fix Trac #2674: in TH reject empty case expressions and function
 definitions
 }}}
 Now from this program
 {{{
 {-# LANGUAGE TemplateHaskell #-}
 import Language.Haskell.TH
 $(return [FunD (mkName foo) []])
 }}}
 we get the more civilised error
 {{{
 T2674.hs:3:2:
 Function binding for `foo' has no equations
 When splicing generated code into the program
 }}}

 Pls merge

 Simon

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


[GHC] #2732: Incorrect requirement for building ghc

2008-10-30 Thread GHC
#2732: Incorrect requirement for building ghc
-+--
Reporter:  jputcu|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Component:  Documentation   
 Version:  6.8.3 |Severity:  normal  
Keywords:|Testcase:  
Architecture:  Unknown/Multiple  |  Os:  Unknown/Multiple
-+--
 At the bottom of http://www.haskell.org/ghc/download_ghc_683.html you'll
 see I need ghc = 6.0 to build ghc-6.8.3.

 In issue #2718 I was told my ghc-6.2.2 was to old to build ghc-6.8.3.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2732
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] #2733: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1

2008-10-30 Thread GHC
#2733: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1
---+
Reporter:  DavidA  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Component:  Compiler
 Version:  6.8.3   |Severity:  normal  
Keywords:  newtype deriving, phantom type  |Testcase:  
Architecture:  x86 |  Os:  Windows 
---+
 Consider the following code:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}

 data Lex
 data Glex

 newtype Monomial ord = M [Int] deriving (Eq,Show)

 instance Ord (Monomial Lex) where
 compare (M xs) (M ys) = compare xs ys

 instance Ord (Monomial Glex) where
 compare (M xs) (M ys) = compare (sum xs, xs) (sum ys, ys)

 -- newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show,Ord)
 newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show)

 instance Ord (Monomial ord) = Ord (Polynomial ord) where
 compare (P ts) (P us) = compare ts us

 In 6.6.1, it was permissible to derive the Ord instance for Polynomial ord
 from the ord instance for Monomial ord - the commented out code would
 compile. In 6.8.1-3, the commented out code doesn't compile, so you have
 to do the derivation by hand, as shown.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2733
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] #2734: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1

2008-10-30 Thread GHC
#2734: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1
---+
Reporter:  DavidA  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Component:  Compiler
 Version:  6.8.3   |Severity:  normal  
Keywords:  newtype deriving, phantom type  |Testcase:  
Architecture:  x86 |  Os:  Windows 
---+
 Consider the following code:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}

 data Lex

 data Glex

 newtype Monomial ord = M [Int] deriving (Eq,Show)

 instance Ord (Monomial Lex) where
 compare (M xs) (M ys) = compare xs ys

 instance Ord (Monomial Glex) where
 compare (M xs) (M ys) = compare (sum xs, xs) (sum ys, ys)

 -- newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show,Ord)

 newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show)

 instance Ord (Monomial ord) = Ord (Polynomial ord) where
 compare (P ts) (P us) = compare ts us

 In 6.6.1, it was permissible to derive the Ord instance for Polynomial ord
 from the ord instance for Monomial ord - the commented out code would
 compile. In 6.8.1-3, the commented out code doesn't compile, so you have
 to do the derivation by hand, as shown.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2734
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] #2734: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1

2008-10-30 Thread GHC
#2734: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1
+---
 Reporter:  DavidA  |  Owner: 
 Type:  bug | Status:  closed 
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.3  
 Severity:  normal  | Resolution:  invalid
 Keywords:  newtype deriving, phantom type  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by simonpj):

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

Old description:

 Consider the following code:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}

 data Lex

 data Glex

 newtype Monomial ord = M [Int] deriving (Eq,Show)

 instance Ord (Monomial Lex) where
 compare (M xs) (M ys) = compare xs ys

 instance Ord (Monomial Glex) where
 compare (M xs) (M ys) = compare (sum xs, xs) (sum ys, ys)

 -- newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show,Ord)

 newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show)

 instance Ord (Monomial ord) = Ord (Polynomial ord) where
 compare (P ts) (P us) = compare ts us

 In 6.6.1, it was permissible to derive the Ord instance for Polynomial
 ord from the ord instance for Monomial ord - the commented out code would
 compile. In 6.8.1-3, the commented out code doesn't compile, so you have
 to do the derivation by hand, as shown.

New description:

 Consider the following code:
 {{{
 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}

 data Lex

 data Glex

 newtype Monomial ord = M [Int] deriving (Eq,Show)

 instance Ord (Monomial Lex) where
 compare (M xs) (M ys) = compare xs ys

 instance Ord (Monomial Glex) where
 compare (M xs) (M ys) = compare (sum xs, xs) (sum ys, ys)

 -- newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show,Ord)

 newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show)

 instance Ord (Monomial ord) = Ord (Polynomial ord) where
 compare (P ts) (P us) = compare ts us
 }}}
 In 6.6.1, it was permissible to derive the Ord instance for Polynomial ord
 from the ord instance for Monomial ord - the commented out code would
 compile. In 6.8.1-3, the commented out code doesn't compile, so you have
 to do the derivation by hand, as shown.

Comment:

 I'm afraid this is by design: the 6.6 deriving mechanism could all-too-
 easily infer a stupid context for the derived instance declaration.

 However 6.10 lets you ''specify'' the context for the derived instance
 declaration (rather than having it inferred) thus:
 {{{
  newtype Polynomial ord = P [Monomial ord] deriving (Eq,Show)

  deriving instance Ord (Monomial ord) = Ord (Polynomial ord)
 }}}
 The `deriving instance` is half way between `deriving(Ord)` and giving a
 full instance declaration, which you didn't want to do.  It's documented
 under standalone deriving in the user manual.

 If the documentation could be improved, I'd welcome concrete suggestions.
 Meanwhile I'm closing the bug.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2734#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] #2733: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1

2008-10-30 Thread GHC
#2733: Newtype deriving over phantom types broke between GHC 6.6.1 and GHC 6.8.1
+---
 Reporter:  DavidA  |  Owner:   
 Type:  bug | Status:  closed   
 Priority:  normal  |  Milestone:   
Component:  Compiler|Version:  6.8.3
 Severity:  normal  | Resolution:  duplicate
 Keywords:  newtype deriving, phantom type  | Difficulty:  Unknown  
 Testcase:  |   Architecture:  x86  
   Os:  Windows |  
+---
Changes (by simonpj):

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

Comment:

 Dup #2734.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2733#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] #2695: bogus syntactically distinct contexts error

2008-10-30 Thread GHC
#2695: bogus syntactically distinct contexts error
-+--
 Reporter:  conal|  Owner:  
 Type:  bug  | Status:  new 
 Priority:  low  |  Milestone:  _|_ 
Component:  Compiler (Type checker)  |Version:  6.11
 Severity:  normal   | Resolution:  
 Keywords:   | Difficulty:  Unknown 
 Testcase:   |   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple |  
-+--
Changes (by simonpj):

  * priority:  normal = low
  * milestone:  6.10.2 = _|_

Comment:

 Good point.  The requirement that the contexts of all the declarations in
 a mutually recursive group must be identical, even though really we have
 polymorphic recursion, is a very tiresome Haskell 98 thing.  What is
 biting us here is that we're trying to unify the two contexts, but since
 `Basis` is a type function, knowing that `(Basis a1)` = `(Basis a2)` does
 not allow us to conclude that `a1` = `a2`.

 We could solve this by writing a syntactic-identity checker (oh, but it
 has to be subject to alpha-renaming...), but it just doesn't seem worth
 the bother.

 The solution is to use `-XRelaxedPolyRec`, which lifts the restriction
 altogether.  Haskell Prime will probably have this as the default.

 Meanwhile I'll leave this open at low priority.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2695#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] #2722: loop when compiling with -O option with ghc-6.10.0.20081019

2008-10-30 Thread GHC
#2722: loop when compiling with -O option with ghc-6.10.0.20081019
---+
 Reporter:  uwe|  Owner: 
 Type:  bug| Status:  new
 Priority:  high   |  Milestone:  6.10.1 
Component:  Compiler   |Version:  6.10.1 
 Severity:  normal | Resolution: 
 Keywords:  Optimization Loop  | Difficulty:  Unknown
 Testcase: |   Architecture:  x86
   Os:  Linux  |  
---+
Comment (by igloo):

 I've attached a single module case:
 {{{
 $ ghc -fforce-recomp --make HXmlParser.hs -Wall  ./HXmlParser
 [1 of 1] Compiling Main ( HXmlParser.hs, HXmlParser.o )
 Linking HXmlParser ...
 Foo 1
 Foo 2
 HXmlParser: XXX
 }}}
 {{{
 $ ghc -fforce-recomp --make HXmlParser.hs -O -Wall  ./HXmlParser
 [1 of 1] Compiling Main ( HXmlParser.hs, HXmlParser.o )
 Linking HXmlParser ...
 Foo 1
 HXmlParser: loop
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2722#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] #2722: loop when compiling with -O option with ghc-6.10.0.20081019

2008-10-30 Thread GHC
#2722: loop when compiling with -O option with ghc-6.10.0.20081019
---+
 Reporter:  uwe|  Owner: 
 Type:  bug| Status:  new
 Priority:  high   |  Milestone:  6.10.1 
Component:  Compiler   |Version:  6.10.1 
 Severity:  normal | Resolution: 
 Keywords:  Optimization Loop  | Difficulty:  Unknown
 Testcase: |   Architecture:  x86
   Os:  Linux  |  
---+
Comment (by simonpj):

 OK I know what is happening.  Sigh.

 I boiled it down still more:
 {{{
 module Foo (main, arid1, arid2) where

 import Prelude hiding (id, (.))
 import qualified Prelude
 import Control.Category
 import Control.Arrow
 import System.IO
 import Debug.Trace


 main = runXIOState arid1-- Loop with arid1
 -- Works with arid2

 arid1 :: Arrow m = m a a
 arid1 = arr id

 arid2 :: Arrow m = m a a
 arid2 = arr Prelude.id

 runXIOState :: IOSLA () c - IO [c]
 runXIOState f = runIOSLA f ()

 newtype IOSLA a b = IOSLA { runIOSLA :: a - IO [b] }

 instance Arrow IOSLA where
 arr f = IOSLA $ \ x - return [f x]

 instance Category IOSLA where
 id = arr id

 -- arr :: Arrow m = (b-c) - m b c
 -- id  :: Category m = m b b
 -- (arr id) :: Arrow m = m a a

 }}}
 What is happening is this.
   * In `Control.Arrow` we find the following rewrite rule
 {{{
 {-# RULES identity arr id = id
 }}}
   * But, as you see above, `id` is defined to be `arr id`.

 So the result is (unsurprisingly) a loop.

 I'm not sure whether the fault lies with the person who wrote the RULE in
 `Control.Arrow`, or the person who wrote the instance of IOSLA above.
 (The instance does look suspicious, because `Category` is a superclass of
 `Arrow`, and yet uses the arrow `arr` method to define `id`.)

 Very tricky to track down.  At all events I say that GHC is not at fault.

 I'm leaving this open because someone should
  * Decide whether the rules in `Control.Arrow` are valid in general.
  * If so, write some documentation somewhere about the constraints that
 these rules impose on instance declarations.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2722#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] #2728: T2627 profasm/profc: Kinds don't match in type application

2008-10-30 Thread GHC
#2728: T2627 profasm/profc: Kinds don't match in type application
--+-
 Reporter:  igloo |  Owner:  
 Type:  bug   | Status:  closed  
 Priority:  normal|  Milestone:  6.10.1  
Component:  Compiler  |Version:  6.10.1  
 Severity:  normal| Resolution:  fixed   
 Keywords:| Difficulty:  Unknown 
 Testcase:  T2627 |   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 Fixed by
 {{{
 Tue Oct 21 15:31:56 BST 2008  [EMAIL PROTECTED]
   * Do proper cloning in worker/wrapper splitting

   See Note [Freshen type variables] in WwLib.  We need to clone type
   variables when building a worker/wrapper split, else we simply get
   bogus code, admittedly in rather obscure situations.  I can't quite
   remember what program showed this up, unfortunately, but there
   definitely *was* one!  (You get a Lint error.)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2728#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] #2674: ghc panic TcPat.checkArgs

2008-10-30 Thread GHC
#2674: ghc panic TcPat.checkArgs
--+-
 Reporter:  rwbarton  |  Owner:  igloo   
 Type:  merge | Status:  closed  
 Priority:  normal|  Milestone:  6.10.1  
Component:  Template Haskell  |Version:  6.8.2   
 Severity:  normal| Resolution:  fixed   
 Keywords:| Difficulty:  Unknown 
 Testcase:  th/T2674  |   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 Merged

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2674#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] #1291: Binary Solaris build fails on Solaris 9

2008-10-30 Thread GHC
#1291: Binary Solaris build fails on Solaris 9
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  closed 
 Priority:  normal|  Milestone:  _|_
Component:  Build System  |Version:  6.6.1  
 Severity:  normal| Resolution:  fixed  
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  sparc  
   Os:  Solaris   |  
--+-
Comment (by guest):

 I'm working on getting this working on solaris 8.  I will post some notes
 once/if I get it working.

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