Re: [GHC] #7242: struct kevent is different on NetBSD

2012-09-28 Thread GHC
#7242: struct kevent is different on NetBSD
-+--
Reporter:  iquiw |   Owner:   
Type:  bug   |  Status:  patch
Priority:  normal|   Milestone:   
   Component:  libraries/base| Version:  7.6.1
Keywords:|  Os:  NetBSD   
Architecture:  Unknown/Multiple  | Failure:  Runtime crash
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--

Comment(by iquiw):

 amend version of FFI-wrapper patch was attached.

-- 
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] #7280: zonkQuantifiedTyVar panic

2012-09-28 Thread GHC
#7280: zonkQuantifiedTyVar panic
--+-
 Reporter:  rl|  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Small program (extracted from the dev version of vector):

 {{{
 {-# LANGUAGE Rank2Types, MultiParamTypeClasses, FlexibleContexts,
 TypeFamilies, ScopedTypeVariables #-}

 module T where

 type family Mutable (v :: * -> *) :: * -> * -> *
 class MVector (v :: * -> * -> *) a
 class MVector (Mutable v) a => Vector v a where
   copy :: Monad m => Mutable v s a -> v a -> m ()

 data Chunk v s a = Chunk (forall m. (Monad m, Vector v a) => Mutable v s a
 -> m ())

 vstep (v:vs) = Chunk (\mv -> copy mv v)
 }}}

 When I compile this, I get:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-unknown-linux):
 zonkQuantifiedTyVar f_afr{tv} [fsk]
 }}}

-- 
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] #7279: warning for unused type variables in instance contexts; -fwarn-unreachable-type-variables?

2012-09-28 Thread GHC
#7279: warning for unused type variables in instance contexts; 
-fwarn-unreachable-
type-variables?
--+-
 Reporter:  nfrisby   |  Owner: 
 Type:  feature request   | Status:  new
 Priority:  normal|  Component:  Compiler (Type checker)
  Version:  7.6.1 |   Keywords: 
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
  Failure:  None/Unknown  |   Testcase: 
Blockedby:|   Blocking: 
  Related:|  
--+-
 I just spend 90 minutes tracking down what ended up being a typo
 introduced via find-and-replace.

 I accidentally introduced a spurious constraint on an instance context:

 {{{
 instance (Monoid m, Context t) => Class t where …
 }}}

 I would like to be warned about constraints on variables that certainly
 have no connection to variables in the instance head. {{{-fwarn-
 unreachable-type-variables}}}?

 This might also help catch those signatures where all occurrences of type
 variable are as index arguments to a type family, rendering the functional
 unusable because of "ambiguous type variable" errors at every call site.

-- 
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] #7278: nonsensical kind variable ascription causes panic

2012-09-28 Thread GHC
#7278: nonsensical kind variable ascription causes panic
+---
 Reporter:  nfrisby |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Component:  Compiler (Type checker)
  Version:  7.6.1   |   Keywords: 
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple   
  Failure:  Compile-time crash  |   Testcase: 
Blockedby:  |   Blocking: 
  Related:  |  
+---

Comment(by nfrisby):

 Whoops — submitted too soon … again; I wish preview worked on comments.

 Replacing {{{t :: k}}} with {{{t}}} in the context in f's signature and
 adding {{{FlexibleContexts}}} avoids the panic.

-- 
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] #7278: nonsensical kind variable ascription causes panic

2012-09-28 Thread GHC
#7278: nonsensical kind variable ascription causes panic
+---
 Reporter:  nfrisby |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Component:  Compiler (Type checker)
  Version:  7.6.1   |   Keywords: 
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple   
  Failure:  Compile-time crash  |   Testcase: 
Blockedby:  |   Blocking: 
  Related:  |  
+---

Comment(by nfrisby):

 Whoops — submitted too soon. Replacing {{{t :: k}}} with {{{t}}} and
 adding {{{FlexibleContexts}}} avoids the panic.

-- 
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] #7278: nonsensical kind variable ascription causes panic

2012-09-28 Thread GHC
#7278: nonsensical kind variable ascription causes panic
+---
 Reporter:  nfrisby |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Component:  Compiler (Type checker)
  Version:  7.6.1   |   Keywords: 
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple   
  Failure:  Compile-time crash  |   Testcase: 
Blockedby:  |   Blocking: 
  Related:  |  
+---
 {{{
 {-# LANGUAGE TypeFamilies, PolyKinds, MultiParamTypeClasses #-}

 module GHCBug where

 type family TF (t  :: k) :: * -> * -> *

 class C (t :: k) (dcs :: * -> * -> *)

 f :: (C (t :: k) (TF t)) => TF t p1 p0 -> t p1 p0
 f = undefined -- panic caused by (t :: k) in the signature's context
 }}}

 gives

 {{{
 [1 of 1] Compiling GHCBug   ( GHCPanic.hs, interpreted )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-apple-darwin):
 metaTvRef
 <>
 }}}

-- 
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] #7274: hp2ps sometimes creates invalid postscript files

2012-09-28 Thread GHC
#7274: hp2ps sometimes creates invalid postscript files
--+-
 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  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by fryguybob):

 It is failing to correctly escape the string on line 318 of the Postscript
 file: `((227)master.\/master/main.\) show`

-- 
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] #7277: Recompilation check fails for TH unless functions are inlined

2012-09-28 Thread GHC
#7277: Recompilation check fails for TH unless functions are inlined
-+--
Reporter:  orenbenkiki   |   Owner: 
Type:  bug   |  Status:  new
Priority:  high  |   Milestone:  7.6.2  
   Component:  Template Haskell  | Version:  7.4.2  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:  481   |  
-+--
Changes (by simonpj):

  * priority:  normal => high
  * difficulty:  => Unknown
  * milestone:  => 7.6.2


Comment:

 Thanks.  We should fix this for 7.8 or even 7.6.2.

-- 
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] #7276: -fdefer-type-errors allows the types of quotations to be coerced, causing segmentation fault

2012-09-28 Thread GHC
#7276: -fdefer-type-errors allows the types of quotations to be coerced, causing
segmentation fault
+---
 Reporter:  parcs   |  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  7.6.1   |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---

Comment(by parcs):

 Oh right, thanks. I meant to say `:t $([d|a = ()|])`

-- 
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] #7276: -fdefer-type-errors allows the types of quotations to be coerced, causing segmentation fault

2012-09-28 Thread GHC
#7276: -fdefer-type-errors allows the types of quotations to be coerced, causing
segmentation fault
+---
 Reporter:  parcs   |  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  7.6.1   |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---

Comment(by guest):

 Just a note: since defering for expressions is off in GHCi by default, the
 error can be reproduced with

 {{{
 let x = $([d|a = ()|])
 }}}

-- 
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] #7277: Recompilation check fails for TH unless functions are inlined

2012-09-28 Thread GHC
#7277: Recompilation check fails for TH unless functions are inlined
-+--
 Reporter:  orenbenkiki  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Template Haskell
  Version:  7.4.2|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:  481  |  
-+--
 Even though [http://hackage.haskell.org/trac/ghc/ticket/481 Issue 481] is
 marked as closed, the fix is only partial. If a function inside $( ... )
 is not inlined, then the dependency check fails. Attached is a full
 example, built around the following code:

 {{{
 #ifdef NO_INLINE
 {-# NOINLINE libraryFunction #-}
 #endif

 libraryFunction :: Q Exp
 libraryFunction = [e| "Return X" |]
 }}}

 And the test:

 {{{
 case_library_function = $( libraryFunction ) @?= "Return A"
 }}}

 Here is are the relevant parts of RUNME.LOG:

 {{{
 + rm -rf dist
 + cabal configure --enable-tests
 Resolving dependencies...
 Configuring dependency-bug-0.0.1...
 + sed -e 's/Return ./Return A/' -i src/Dependency/Library.hs
 + cabal build
 Building dependency-bug-0.0.1...
 Preprocessing library dependency-bug-0.0.1...
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.o )
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.p_o )
 Registering dependency-bug-0.0.1...
 Preprocessing test suite 'Test' for dependency-bug-0.0.1...
 [1 of 1] Compiling Main ( test/Main.hs, dist/build/Test/Test-
 tmp/Main.o )
 Linking dist/build/Test/Test ...
 + cabal test
 Running 1 test suites...
 Test suite Test: RUNNING...
 Test suite Test: PASS
 Test suite logged to: dist/test/dependency-bug-0.0.1-Test.log
 1 of 1 test suites (1 of 1 test cases) passed.
 + sed -e 's/Return ./Return B/' -i src/Dependency/Library.hs
 + cabal build
 Building dependency-bug-0.0.1...
 Preprocessing library dependency-bug-0.0.1...
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.o )
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.p_o )
 Registering dependency-bug-0.0.1...
 Preprocessing test suite 'Test' for dependency-bug-0.0.1...
 [1 of 1] Compiling Main ( test/Main.hs, dist/build/Test/Test-
 tmp/Main.o )
 Linking dist/build/Test/Test ...
 + cabal test
 Running 1 test suites...
 Test suite Test: RUNNING...
 Main:
   library function: [Failed]
 expected: "Return A"
  but got: "Return B"

  Test Cases  Total
  Passed  0   0
  Failed  1   1
  Total   1   1
 Test suite Test: FAIL
 Test suite logged to: dist/test/dependency-bug-0.0.1-Test.log
 0 of 1 test suites (0 of 1 test cases) passed.

 }}}

 This is as expected; we changed the source to "Return B" but the test
 expects the library to "Return A" so it fails. So far, so good. However:

 {{{
 + rm -rf dist
 + cabal configure --enable-tests -fwithout-inline
 Resolving dependencies...
 Configuring dependency-bug-0.0.1...
 + sed -e 's/Return ./Return A/' -i src/Dependency/Library.hs
 + cabal build
 Building dependency-bug-0.0.1...
 Preprocessing library dependency-bug-0.0.1...
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.o )
 [1 of 1] Compiling Dependency.Library ( src/Dependency/Library.hs,
 dist/build/Dependency/Library.p_o )
 Registering dependency-bug-0.0.1...
 Preprocessing test suite 'Test' for dependency-bug-0.0.1...
 [1 of 1] Compiling Main ( test/Main.hs, dist/build/Test/Test-
 tmp/Main.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package array-0.4.0.0 ... linking ... done.
 Loading package deepseq-1.3.0.0 ... linking ... done.
 Loading package containers-0.4.2.1 ... linking ... done.
 Loading package pretty-1.1.1.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Loading package dependency-bug-0.0.1 ... linking ... done.
 Loading package filepath-1.3.0.0 ... linking ... done.
 Loading package old-locale-1.0.0.4 ... linking ... done.
 Loading package old-time-1.1.0.0 ... linking ... done.
 Loading package bytestring-0.9.2.1 ... linking ... done.
 Loading package unix-2.5.1.1 ... linking ... done.
 Loading package directory-1.1.0.2 ... linking ... done.
 Loading package cpphs-1.14 ... linking ... done.
 Loading package haskell-src-exts-1.13.5 ... linking ... done.
 Loading p

Re: [GHC] #6024: Allow defining kinds alone, without a datatype

2012-09-28 Thread GHC
#6024: Allow defining kinds alone, without a datatype
+---
Reporter:  dreixel  |   Owner:  
Type:  feature request  |  Status:  new 
Priority:  normal   |   Milestone:  7.8.1   
   Component:  Compiler (Type checker)  | Version:  7.5 
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---
Changes (by igloo):

  * difficulty:  => Unknown
  * milestone:  => 7.8.1


Comment:

 Is it clear that being able to use the same names for different things
 won't cause too much confusion?

 I guess that we manage fine with constructors and types sharing names, so
 perhaps there is no problem with types and kinds.

 Are there any plans to have support for "sorts" and above in GHC? If so,
 would each level have its own namespace?

-- 
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] #3591: A working program reports <> when compiled with -O

2012-09-28 Thread GHC
#3591: A working program reports <> when compiled with -O
-+--
  Reporter:  blamario|  Owner:  igloo 
  Type:  merge   | Status:  closed
  Priority:  normal  |  Milestone:  6.12.1
 Component:  Compiler|Version:  6.10.4
Resolution:  fixed   |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  None/Unknown| Difficulty:  Unknown   
  Testcase:  simplCore/should_run/T3591  |  Blockedby:
  Blocking:  |Related:
-+--

Comment(by simonpj):

 The output comes from debug traces, which are bound to be fragile.  I'm
 just accepting the output for now.

 Simon

-- 
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] #6017: Reading ./.ghci files raises security issues

2012-09-28 Thread GHC
#6017: Reading ./.ghci files raises security issues
-+--
Reporter:  nomeata   |   Owner:  
Type:  task  |  Status:  new 
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:|  
-+--
Changes (by igloo):

  * priority:  normal => high
  * difficulty:  => Unknown
  * milestone:  => 7.8.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


[GHC] #7276: -fdefer-type-errors allows the types of quotations to be coerced, causing segmentation fault

2012-09-28 Thread GHC
#7276: -fdefer-type-errors allows the types of quotations to be coerced, causing
segmentation fault
+---
 Reporter:  parcs   |  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  7.6.1   |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---
 `-fdefer-type-errors` allows the type of a quotation to be coerced into
 another quotation type. This allows e.g. a declaration quotation to be
 used in a place where an expression quotation is expected, which results
 in a compile-time segmentation fault.

 The following GHCi script demonstrates the issue:

 {{{
 :set -fdefer-type-errors
 :set -XTemplateHaskell
 $([d|a = ()|])
 }}}

-- 
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] #7274: hp2ps sometimes creates invalid postscript files

2012-09-28 Thread GHC
#7274: hp2ps sometimes creates invalid postscript files
--+-
 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  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by edsko):

 (Incidentally, a workaround is using hp2pretty.)

-- 
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] #7275: Give more detailed information about PINNED data in a heap profile

2012-09-28 Thread GHC
#7275: Give more detailed information about PINNED data in a heap profile
--+-
 Reporter:  edsko |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 This is particularly useful when tracking down memory leaks due to
 retaining (sub)bytestrings which themselves retain larger bytestrings. At
 the moment, all the profile tells us is that this memory is "PINNED" but
 it doesn't give us any info at all as to where the memory was allocated.

-- 
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] #7274: hp2ps sometimes creates invalid postscript files

2012-09-28 Thread GHC
#7274: hp2ps sometimes creates invalid postscript files
--+-
 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  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 The attached .hp file is one example; running the resulting ps file
 through ps2pdf gives


 Error: /syntaxerror in -file-
 Operand stack:

 Execution stack:
%interp_exit   .runexec2   --nostringval--   --nostringval--
 --nostringval--   2   %stopped_push   --nostringval--   --nostringval--
 --nostringval--   false   1   %stopped_push   1894   1   3   %oparray_pop
 1893   1   3   %oparray_pop   1877   1   3   %oparray_pop   1771   1   3
 %oparray_pop   --nostringval--   %errorexec_pop   .runexec2
 --nostringval--   --nostringval--   --nostringval--   2   %stopped_push
 Dictionary stack:
--dict:1157/1684(ro)(G)--   --dict:0/20(G)--   --dict:79/200(L)--
 Current allocation mode is local
 Last OS error: 2
 Current file position is 12516
 GPL Ghostscript 9.05: Unrecoverable error, exit code 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] #7272: PolyKinds and mutually recursive modules

2012-09-28 Thread GHC
#7272: PolyKinds and mutually recursive modules
--+-
 Reporter:  dreixel   |  Owner:  dreixel 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
Changes (by dreixel):

  * owner:  => dreixel


Comment:

 I'll look into this.

-- 
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] #7273: Binary size increase in nofib/grep between 7.6.1 and HEAD

2012-09-28 Thread GHC
#7273: Binary size increase in nofib/grep between 7.6.1 and HEAD
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 While browsing the nofib results comparing 7.6.1 and HEAD today, I noticed
 that binary sizes for `grep` are significantly larger in HEAD:

 {{{
 grep
Main34706  +31.3%
 Parsers 5791   +3.2%
 StringMatch28227  +36.9%
 }}}

 The increase seems to be happening in the simplifier, going by the code-
 size stats generated by `-v`.  This probably warrants investigation before
 7.8.1.

 Binary sizes are slightly larger across the board (1-2%), which is at
 least partly due to the new code generator, however performance is
 slightly better (2-3%), if these numbers are to be believed.

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