Re: [GHC] #6040: Adding a type signature changes heap allocation into stack allocation without changing the actual type

2012-04-25 Thread GHC
#6040: Adding a type signature changes heap allocation into stack allocation
without changing the actual type
-+--
Reporter:  tibbe |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 Can you give a repo case that shows a performance effect?

 I'm guessing, but I think that the difference is something like this:
 {{{
 f1 x = g 100   f2 x = g x 0
   where  where
 g 0 = xg x 0 = x
 g n = g (n-1)  g x n = g x (n-1)
 }}}
  * In `f1` we'll heap-allocate a function closure capturing the free
 variable `x`, but the recursive calls have just one argument (plus one for
 the function closure itself).
  * In `f2` we'll pass `x` as an argument.  Indeed `g` will be floated out
 to be a top-level function.  (And in the example you give I don't
 undersatnd why `go` and `insert` are separate functions, but that's a
 stylistic thing.)

 If there were 100 free varaibles instead of 1, it might well be a good
 plan to use `f1`, to save passing 100 arguments in each call.  But since
 there is only one it'd be better to turn the free variable into an
 argument, by lambda lifting.  This is the reverse of the static argument
 transformation.

 The transformation should be done right at the end, because in general
 turning a free varaible into an argument is a bad idea (loss of
 information).

 I've been meaning to do this for some time; if you have data to show it's
 important I could up the priority!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6040#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] #6041: Program hangs when run under Ubuntu Precise

2012-04-25 Thread GHC
#6041: Program hangs when run under Ubuntu Precise
-+--
Reporter:  dsf   |   Owner:   
Type:  bug   |  Status:  infoneeded   
Priority:  high  |   Milestone:  7.4.2
   Component:  Compiler  | Version:  7.4.1
Keywords:|  Os:  Linux
Architecture:  Unknown/Multiple  | Failure:  Runtime crash
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by simonmar):

  * priority:  normal = high
  * difficulty:  = Unknown
  * status:  new = infoneeded
  * milestone:  = 7.4.2


Comment:

 Could you collect some more information for me:

  * Compile with `-debug`, run with `+RTS -Ds` (both a working and a
 failing run)
  * run under `strace` (both a working and a failing run)

 You didn't mention whether this was with `-threaded` or not.  Does that
 make a difference?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6041#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 I noticed today that our binary dists are getting bigger:

 {{{
 -rw-rw-r-- 1 simonmar GHC 118924739 2010-11-17 04:02 ghc-7.0.1-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 112074889 2011-03-02 04:19 ghc-7.0.2-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 109012585 2011-03-27 05:21 ghc-7.0.3-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 109012197 2011-06-15 04:25 ghc-7.0.4-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 115102248 2011-08-10 03:17 ghc-7.2.1-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 114428608 2011-11-10 04:28 ghc-7.2.2-i386
 -unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 123417972 2012-04-20 04:23
 ghc-7.4.1.20120416-i386-unknown-linux.tar.bz2
 -rw-rw-r-- 1 simonmar GHC 144861355 2012-04-18 06:25 ghc-7.5.20120413-i386
 -unknown-linux.tar.bz2
 }}}

 I looked into the difference between 7.0.4 and 7.4.1, and found that it
 seems to be mostly caused by GHC itself getting bigger:

 {{{
 -rwxrwxr-x simonmar/GHC 31280127 2011-06-14 19:59
 ghc-7.0.4/ghc/stage2/build/tmp/ghc-stage2
 -rwxrwxr-x simonmar/GHC 41050757 2012-04-19 20:12
 ghc-7.4.1/ghc/stage2/build/tmp/ghc-stage2
 }}}

 the GHC binary is 25% larger, and the binary dist contains several copies
 of GHC (.a, _p.a, .so, the GHC binary, haddock).

 We didn't add 25% more code to GHC between 7.0.4 and 7.4.1, so why is it
 25% larger?  This increase isn't reflected in other libraries - in fact,
 the base package is smaller in 7.4.1 than 7.0.4.

 I have a horrid feeling that this is due to heavy use of INLINE/INLINABLE
 in `containers`, but I hope I'm wrong.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042
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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by igloo):

 ghc-7.5.20120413 is bigger because it contains dph, parallel, primitive,
 random, stm and vector.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6043: ARM build fails

2012-04-25 Thread GHC
#6043: ARM build fails
-+--
 Reporter:  kgardas  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.5  |   Keywords:  
   Os:  Linux|   Architecture:  arm 
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 Since the half of February 2012, GHC HEAD builds fails on ARM with
 following error:
 {{{
 cp -p ghc/stage2/build/tmp/ghc-stage2 inplace/lib/ghc-stage2
 rm -f  inplace/bin/ghc-stage2
 echo '#!/bin/sh'  inplace/bin/ghc-stage2
 echo 'executablename=/buildbot/ghc-head-
 builder/builder/tempbuild/build/inplace/lib/ghc-stage2'
 inplace/bin/ghc-stage2
 echo 'datadir=/buildbot/ghc-head-
 builder/builder/tempbuild/build/inplace/lib'inplace/bin/ghc-
 stage2
 echo 'bindir=/buildbot/ghc-head-
 builder/builder/tempbuild/build/inplace/bin' inplace/bin/ghc-
 stage2
 echo 'topdir=/buildbot/ghc-head-
 builder/builder/tempbuild/build/inplace/lib'  inplace/bin/ghc-
 stage2
 echo 'pgmgcc=/usr/bin/gcc' inplace/bin/ghc-stage2
 cat ghc/ghc.wrapperinplace/bin/ghc-stage2
 chmod +x   inplace/bin/ghc-stage2
 inplace/bin/ghc-stage2   -H32m -O-hide-all-packages -i
 -iutils/haddock/src -iutils/haddock/dist/build
 -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build
 -Iutils/haddock/dist/build/autogen-optP-DIN_GHC_TREE -optP-include
 -optPutils/haddock/dist/build/autogen/cabal_macros.h -package Cabal-1.14.0
 -package array-0.3.0.3 -package base-4.5.0.0 -package containers-0.5.0.0
 -package directory-1.1.0.1 -package filepath-1.2.0.1 -package
 ghc-7.5.20120423 -package pretty-1.1.1.0 -package xhtml-3000.2.0.5
 -funbox-strict-fields -O2 -Wall -fwarn-tabs -XHaskell2010 -XCPP
 -XDeriveDataTypeable -XScopedTypeVariables -XMagicHash  -no-user-package-
 conf -rtsopts -odir utils/haddock/dist/build -hidir
 utils/haddock/dist/build -stubdir utils/haddock/dist/build -hisuf hi -osuf
 o -hcsuf hc -c utils/haddock/src/Haddock/GhcUtils.hs -o
 utils/haddock/dist/build/Haddock/GhcUtils.o

 utils/haddock/src/Haddock/GhcUtils.hs:274:21:
 Illegal record syntax (use -XTraditionalRecordSyntax): d {objectDir =
 Just
 f}
 make[1]: *** [utils/haddock/dist/build/Haddock/GhcUtils.o] Error 1
 make: *** [all] Error 2
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6043
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] #5914: armhf build fails in Ubuntu (7.4.1)

2012-04-25 Thread GHC
#5914: armhf build fails in Ubuntu (7.4.1)
-+--
 Reporter:  jani@…   |  Owner:  kgardas
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  Compiler (LLVM)
  Version:  7.4.1|   Keywords: 
   Os:  Linux|   Architecture:  arm
  Failure:  Building GHC failed  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--

Comment(by kgardas):

 Hi, attached patch adds hard-float ABI support to GHC HEAD. I've
 bootstrapped this on x86-solaris w/o any issue and also up to the ghc-
 stage2 failure (#6043) on ARM/Ubuntu with hard-float ABI. I'm not able to
 test it due to #6043 yet.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5914#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 milan: great (I hoped by CC'ing you I might prompt you to run some tests
 :-)

 My worry is that INLINABLE is causing us to specialise e.g.
 `Data.IntMap.lookup` every time it is used.  If that is the case, then we
 should write a wrapper module around `Data.IntMap` and use it everywhere
 in GHC.  We do this to some extent (`UniqFM`) but not everywhere, and we
 should also check that in the case of `UniqFM` it really is sharing the
 specialisations as we expect.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 igloo: I wasn't expecting the extra packages to be in the bindist.
 Looking at the code it seems that `InstallExtraPackages` should be `NO`,
 which ought to prevent them going into the bindist.  Any idea what's going
 on?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6036: Kind generalization fails in data family instance GADT

2012-04-25 Thread GHC
#6036: Kind generalization fails in data family instance GADT
---+
 Reporter:  goldfire   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.5|   Keywords:
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+

Comment(by simonpj@…):

 commit 2316a90da6e78349874a181baa762ef60c80333e
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Apr 25 12:56:44 2012 +0100

 More fixes to kind polymorphism, fixes Trac #6035, #6036

 * Significant refactoring in tcFamPats and tcConDecl

 * It seems that we have to allow KindVars (not just
   TcKindVars during kind unification.  See
   Note [Unifying kind variables] in TcUnify.

 * Be consistent about zonkQuantifiedTyVars

 * Split the TcType-TcType zonker (in TcMType)
from the TcType-Type   zonker (in TcHsSyn)
   The clever parameterisation was doing my head in,
   and it's only a small function

 * Remove some dead code (tcTyVarBndrsGen)

  compiler/ghci/RtClosureInspect.hs   |4 +-
  compiler/typecheck/FamInst.lhs  |   11 ++--
  compiler/typecheck/TcHsSyn.lhs  |   90 ---
  compiler/typecheck/TcHsType.lhs |   65 ---
  compiler/typecheck/TcMType.lhs  |   79 ---
  compiler/typecheck/TcTyClsDecls.lhs |  120
 +++---
  compiler/typecheck/TcUnify.lhs  |   67 +++-
  7 files changed, 221 insertions(+), 215 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6036#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] #6039: Ill-sorted kinds crash GHC

2012-04-25 Thread GHC
#6039: Ill-sorted kinds crash GHC
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj@…):

 commit a40ee020b53d3b397d24f4addeda78945e72292a
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Apr 25 09:37:53 2012 +0100

 Better error messages during sort checking of kind signatures

 Fixes Trac #6039, where we have a bogus kind signature
data T (a :: j k) = MkT

  compiler/typecheck/TcHsType.lhs |   63
 ++
  compiler/typecheck/TcTyClsDecls.lhs |2 +
  2 files changed, 35 insertions(+), 30 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6039#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] #6035: Kind-indexed type family failure with polymorphic kinds

2012-04-25 Thread GHC
#6035: Kind-indexed type family failure with polymorphic kinds
--+-
 Reporter:  goldfire  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Component:  Compiler (Type checker)
  Version:  7.5   |   Keywords:  PolyKinds TypeFamilies 
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
  Failure:  None/Unknown  |   Testcase: 
Blockedby:|   Blocking: 
  Related:|  
--+-

Comment(by simonpj@…):

 commit 2316a90da6e78349874a181baa762ef60c80333e
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Apr 25 12:56:44 2012 +0100

 More fixes to kind polymorphism, fixes Trac #6035, #6036

 * Significant refactoring in tcFamPats and tcConDecl

 * It seems that we have to allow KindVars (not just
   TcKindVars during kind unification.  See
   Note [Unifying kind variables] in TcUnify.

 * Be consistent about zonkQuantifiedTyVars

 * Split the TcType-TcType zonker (in TcMType)
from the TcType-Type   zonker (in TcHsSyn)
   The clever parameterisation was doing my head in,
   and it's only a small function

 * Remove some dead code (tcTyVarBndrsGen)

  compiler/ghci/RtClosureInspect.hs   |4 +-
  compiler/typecheck/FamInst.lhs  |   11 ++--
  compiler/typecheck/TcHsSyn.lhs  |   90 ---
  compiler/typecheck/TcHsType.lhs |   65 ---
  compiler/typecheck/TcMType.lhs  |   79 ---
  compiler/typecheck/TcTyClsDecls.lhs |  120
 +++---
  compiler/typecheck/TcUnify.lhs  |   67 +++-
  7 files changed, 221 insertions(+), 215 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6035#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] #5867: Include use site of deprecated identifiers in deprecation warnings

2012-04-25 Thread GHC
#5867: Include use site of deprecated identifiers in deprecation warnings
-+--
Reporter:  SimonHengel   |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj@…):

 commit bcff115ac5ae97ce02ac366313d117830b99af45
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Apr 25 08:21:13 2012 +0100

 Report deprecations at occurrence sites, not once per module

 Fixes Trac #5867, and is generally nicer

  compiler/iface/LoadIface.lhs  |2 +-
  compiler/rename/RnEnv.lhs |   93
 +--
  compiler/rename/RnNames.lhs   |   98
 ++--
  compiler/typecheck/TcRnDriver.lhs |   21 
  4 files changed, 105 insertions(+), 109 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5867#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] #6005: Template Haskell disallows use of promoted data constructor in same splice

2012-04-25 Thread GHC
#6005: Template Haskell disallows use of promoted data constructor in same 
splice
---+
 Reporter:  goldfire   |  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Component:  Template Haskell   
  Version:  7.5|   Keywords:  DataKinds PolyKinds
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple   
  Failure:  GHC rejects valid program  |   Testcase: 
Blockedby: |   Blocking: 
  Related: |  
---+

Comment(by simonpj@…):

 commit 2a1190431218f838797be3c09084e22dc131c58a
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Apr 25 12:55:41 2012 +0100

 Fix looking up of Exact RdrNames, fixes Trac #6005

 See Note [Splicing Exact names] in RnEnv.

  compiler/rename/RnEnv.lhs |   43
 ++-
  1 files changed, 34 insertions(+), 9 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6005#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by milan):

 The INLINABLE is being used only on Map and Set.

 The idea is that Data.Map.lookup is specialized if it is used with a known
 class instance (e.g., when using lookup on 'Map Int something'). In that
 case, a specialization is created, together with a rewrite rule which
 causes that this specialization is used for further lookups on 'Map Int
 something'. This rule is used in the same module and also in all modules
 importing this one.

 If we decide to write a wrapper, it would have to mention all key types
 for which a Map or Set is being used. But if I recall, Maps and Sets are
 not frequently used. We'll see from the numbers.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 INLINABLE should only mean that you specialise `Data.Map.lookup` once per
 '''module''', not once per '''call'''.

 Moreover if A imports B (transitively), and B has specialised
 `Data.Map.lookup` at `Int`, then A should not re-specialise it.  So it's
 pretty good actually.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 milan, simonpj: yes, I know how specialisations are shared.  I'm worried
 that we might not be getting the sharing because there isn't a module
 higher up in the hierarchy that creates the specialisation, so that we get
 one copy of `Data.Map.lookup` in each of the leaf modules.

 But anyway it does seem unlikely that this alone could be responsible for
 GHC getting heavier by 10MB, so further investigation is definitely called
 for.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #5867: Include use site of deprecated identifiers in deprecation warnings

2012-04-25 Thread GHC
#5867: Include use site of deprecated identifiers in deprecation warnings
--+-
  Reporter:  SimonHengel  |  Owner:  
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.4.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown | Difficulty:  Unknown 
  Testcase:  rename/should_compile/T5867  |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonpj):

  * status:  new = closed
  * testcase:  = rename/should_compile/T5867
  * resolution:  = fixed


Comment:

 I think you are right, and I've implemented the change.  Thanks.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5867#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] #6039: Ill-sorted kinds crash GHC

2012-04-25 Thread GHC
#6039: Ill-sorted kinds crash GHC
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.4.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  polykinds/T6039   |  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * status:  new = closed
  * testcase:  = polykinds/T6039
  * resolution:  = fixed


Comment:

 Better message
 {{{
 T6039.hs:5:14:
 Kind variable `j' cannot appear in a function position
 In the kind `j k'
 In the data declaration for `T'
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6039#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] #6005: Template Haskell disallows use of promoted data constructor in same splice

2012-04-25 Thread GHC
#6005: Template Haskell disallows use of promoted data constructor in same 
splice
+---
  Reporter:  goldfire   |  Owner: 
  Type:  bug| Status:  closed 
  Priority:  normal |  Milestone: 
 Component:  Template Haskell   |Version:  7.5
Resolution:  fixed  |   Keywords:  DataKinds PolyKinds
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple   
   Failure:  GHC rejects valid program  | Difficulty:  Unknown
  Testcase:  th/T6005   |  Blockedby: 
  Blocking: |Related: 
+---
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed
  * testcase:  = th/T6005


Comment:

 Thanks for pointing me to this.  Fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6005#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] #6036: Kind generalization fails in data family instance GADT

2012-04-25 Thread GHC
#6036: Kind generalization fails in data family instance GADT
+---
  Reporter:  goldfire   |  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  Compiler (Type checker)|Version:  7.5 
Resolution:  fixed  |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  GHC rejects valid program  | Difficulty:  Unknown 
  Testcase:  polykinds/T6036|  Blockedby:  
  Blocking: |Related:  
+---
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed
  * testcase:  = polykinds/T6036


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6036#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] #6009: The packaging used to provide GHC 7.0.4 for OS X fails for 32 bit -- cannot install

2012-04-25 Thread GHC
#6009: The packaging used to provide GHC 7.0.4 for OS X fails for 32 bit -- 
cannot
install
---+
  Reporter:  InvisibleTech |  Owner: 
  Type:  bug   | Status:  closed 
  Priority:  normal|  Milestone: 
 Component:  None  |Version:  7.0.4  
Resolution:  wontfix   |   Keywords: 
Os:  Unknown/Multiple  |   Architecture:  x86
   Failure:  None/Unknown  | Difficulty:  Unknown
  Testcase:|  Blockedby: 
  Blocking:|Related: 
---+

Comment(by marlowsd@…):

 commit 84d79a2a1f5aa16fffbc1451d229930abf8da36b
 {{{
 Author: Simon Marlow marlo...@gmail.com
 Date:   Mon Apr 16 14:54:45 2012 +0100

 distclean was removing ghc-pwd/dist, should be ghc-pwd/dist-boot

 This has been causing bloat in the src dist for ages.

 Noticed while looking at #6009, but I don't think this is the bug
 (./configure always removes ghc-pwd/dist-boot before building ghc-pwd)

  ghc.mk |2 +-
  1 files changed, 1 insertions(+), 1 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6009#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] #6027: Allow changing fixity of new type operators

2012-04-25 Thread GHC
#6027: Allow changing fixity of new type operators
-+--
Reporter:  atnnn |   Owner:  pcapriotti  
Type:  feature request   |  Status:  patch   
Priority:  normal|   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.5 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by pcapriotti):

  * status:  new = patch


Comment:

 I believe the current behavior is just an unintended consequence of the
 new type operator syntax.

 Fixity declarations are already resolved in the `TcClsName` namespace, but
 only if the reader name is in `DataName`.

 The attached patch relaxes this constraints, and always looks up fixity
 declaration names in `TcClsName`, as well as the original namespace.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6027#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] #6038: Allow view patterns inside record patterns

2012-04-25 Thread GHC
#6038: Allow view patterns inside record patterns
-+--
Reporter:  akio  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  _|_ 
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown
  * milestone:  = _|_


Comment:

 I agree that would be nice.  At the moment view patterns must have parens
 around them, and for a good reason. Consider a case with a view pattern:
 {{{
case c of
   (ch - Just y) - y
 }}}
 Now imagine it without parens
 {{{
case c of
   ch - Just y - y}}}
 }}}
 and you can see that you'd need a lot of lookahead to spot where the
 pattern ends.

 There's probably a way to work this out (require parens just for view
 patterns in a case or lambda pattern, somehow?).  If anyone would like to,
 please go ahead and propose (and test!) a patch to the parser.

 Thinking it might be easy, I tried the diff below, but it doesn't work for
 the above reason.  So I'm backing off.

 {{{
 diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp
 index 04c858a..7da62f7 100644
 --- a/compiler/parser/Parser.y.pp
 +++ b/compiler/parser/Parser.y.pp
 @@ -1376,6 +1376,7 @@ exp   :: { LHsExpr RdrName }
  | infixexp '-' exp { LL $ HsArrApp $3 $1
 placeHolderType HsFirstOrderApp False }
  | infixexp '-' exp{ LL $ HsArrApp $1 $3
 placeHolderType HsHigherOrderApp True }
  | infixexp '-' exp{ LL $ HsArrApp $3 $1
 placeHolderType HsHigherOrderApp False}
 +| infixexp '-' exp { LL $ EViewPat $1 $3 }
  | infixexp  { $1 }

  infixexp :: { LHsExpr RdrName }
 @@ -1534,7 +1535,7 @@ texp :: { LHsExpr RdrName }
  | qopm infixexp   { LL $ SectionR $1 $2 }

 -- View patterns get parenthesized above
 -| exp '-' texp   { LL $ EViewPat $1 $3 }
 +--| exp '-' texp   { LL $ EViewPat $1 $3 }
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6038#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] #6021: panic with scoped kind variables

2012-04-25 Thread GHC
#6021: panic with scoped kind variables
-+--
  Reporter:  atnnn   |  Owner:  
  Type:  bug | Status:  closed  
  Priority:  normal  |  Milestone:  
 Component:  Compiler|Version:  7.5 
Resolution:  fixed   |   Keywords:  
Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
   Failure:  Compile-time crash  | Difficulty:  Unknown 
  Testcase:  polykinds/T6021 |  Blockedby:  
  Blocking:  |Related:  
-+--
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed
  * testcase:  = polykinds/T6021


Comment:

 Thank you. Fixed.
 {{{
 T6021.hs:5:22:
 Type variable `b' used as a kind
 In the kind `b'
 In the instance declaration for `Panic (a :: b) b'
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6021#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] #6041: Program hangs when run under Ubuntu Precise

2012-04-25 Thread GHC
#6041: Program hangs when run under Ubuntu Precise
-+--
Reporter:  dsf   |   Owner:   
Type:  bug   |  Status:  infoneeded   
Priority:  high  |   Milestone:  7.4.2
   Component:  Compiler  | Version:  7.4.1
Keywords:|  Os:  Linux
Architecture:  Unknown/Multiple  | Failure:  Runtime crash
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--

Comment(by dsf):

 Up until now we have been using the -threaded option, but I removed it for
 these tests and the behavior is the same.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6041#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] #6041: Program hangs when run under Ubuntu Precise

2012-04-25 Thread GHC
#6041: Program hangs when run under Ubuntu Precise
-+--
Reporter:  dsf   |   Owner:   
Type:  bug   |  Status:  new  
Priority:  high  |   Milestone:  7.4.2
   Component:  Compiler  | Version:  7.4.1
Keywords:|  Os:  Linux
Architecture:  Unknown/Multiple  | Failure:  Runtime crash
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by simonmar):

  * status:  infoneeded = new


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6041#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] #6005: Template Haskell disallows use of promoted data constructor in same splice

2012-04-25 Thread GHC
#6005: Template Haskell disallows use of promoted data constructor in same 
splice
+---
  Reporter:  goldfire   |  Owner: 
  Type:  bug| Status:  new
  Priority:  normal |  Milestone: 
 Component:  Template Haskell   |Version:  7.5
Resolution: |   Keywords:  DataKinds PolyKinds
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple   
   Failure:  GHC rejects valid program  | Difficulty:  Unknown
  Testcase:  th/T6005   |  Blockedby: 
  Blocking: |Related: 
+---
Changes (by goldfire):

  * status:  closed = new
  * resolution:  fixed =


Comment:

 Thanks for applying this fix. Unfortunately, the following case still
 fails:

 {{{
 $( [d|
   data Nat = Zero | Succ Nat deriving Show
   data Proxy a = Proxy
   foo :: Proxy Zero
   foo = Proxy
   |])
 }}}

 The only difference between this case and the original is the {{{deriving
 Show}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6005#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by milan):

 I compiled current GHC head, 7.5.20120425, on x86_64. In all cases I did a
 clean build with GhcLibWays = v and measured size of stripped ghc-stage2:

 {{{
 containers used| ghc-stage2 size | change
 against first line
 
---+-+-
 default containers from GHC tree   | 35888944|
 INLINABLE pragma removed   | 35705456| -0.51%
 INLINABLE pragma removed, INLINE folds removed | 35401680| -1.35%
 INLINABLE changed to INLINE| 35973712| +0.23%
 }}}

 The INLINABLE pragma itself is causing ~183k increase in size (0.5%). If
 INLINE were used instead of INLINABLE, the increase would be ~268k. So
 there is some improvement in using INLINABLE instead of INLINE, but not
 very big.

 Another issue is that containers do INLINE folds. This is a big
 performance win in some circumstances, especially when the combining
 function is small and its unfolding is known. This causes another ~303k
 increase in size (0.8%). BTW, Data.List.foldr is INLINEd too.

 So although there is some code growth, it is not enormous (at least in my
 opinion).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #6042: GHC is bloated

2012-04-25 Thread GHC
#6042: GHC is bloated
-+--
Reporter:  simonmar  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by milan):

 BTW, when I preparing for the advanced functional programming course, I
 found out that the following code

 {{{
 module Test where
 factorial :: Int - Int
 factorial n | n  0 = f n 1
   where f 0 acc = acc
 f n acc = f (n-1) (n * acc)
 }}}

 produces the following STG, on both GHC 7.0.4 and 7.4.1, with unused
 method `factorial_f`:

 {{{
 Test.factorial2 =
 \u srt:(0,*bitmap*) []
 Control.Exception.Base.patError
 a.hs:(4,1)-(6,35)|function factorial;
 SRT(Test.factorial2): [Control.Exception.Base.patError]
 Test.$wf =
 \r [ww_srk ww1_sro]
 case ww_srk of wild_srm {
   __DEFAULT -
   case *# [wild_srm ww1_sro] of sat_srK {
 __DEFAULT -
 case -# [wild_srm 1] of sat_srL {
   __DEFAULT - Test.$wf sat_srL sat_srK;
 };
   };
   0 - ww1_sro;
 };
 SRT(Test.$wf): []
 Test.factorial_f =
 \r [w_srs w1_srv]
 case w_srs of w2_srN {
   GHC.Types.I# ww_sry -
   case w1_srv of w3_srM {
 GHC.Types.I# ww1_srz -
 case Test.$wf ww_sry ww1_srz of ww2_srB {
   __DEFAULT - GHC.Types.I# [ww2_srB];
 };
   };
 };
 SRT(Test.factorial_f): []
 Test.factorial1 = NO_CCS GHC.Types.I#! [1];
 SRT(Test.factorial1): []
 Test.factorial =
 \r srt:(0,*bitmap*) [n_srD]
 case n_srD of wild_srP {
   GHC.Types.I# x_srG -
   case # [x_srG 0] of wild1_srO {
 GHC.Types.False - Test.factorial2;
 GHC.Types.True -
 case Test.$wf x_srG 1 of ww_srJ {
   __DEFAULT - GHC.Types.I# [ww_srJ];
 };
   };
 };
 SRT(Test.factorial): [Test.factorial2]
 }}}
 The `Test.factorial_f` appears also in asm and in the object file.

 I am not saying this is responsible for 10MB code size increase, as
 already GHC 7.0.4 behaves this way, and `--split-objs` should avoid
 linking it into the final executable. But I was surprised.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6042#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] #3699: Wildcards in type functions

2012-04-25 Thread GHC
#3699: Wildcards in type functions
--+-
Reporter:  MartijnVanSteenbergen  |   Owner:  
Type:  feature request|  Status:  new 
Priority:  low|   Milestone:  7.6.1   
   Component:  Compiler   | Version:  6.10.4  
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty: |Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-
Changes (by goldfire):

 * cc: eir@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3699#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] #2189: hSetBuffering stdin NoBuffering doesn't work on Windows

2012-04-25 Thread GHC
#2189: hSetBuffering stdin NoBuffering doesn't work on Windows
-+--
  Reporter:  FalconNL|  Owner:
  Type:  bug | Status:  new   
  Priority:  normal  |  Milestone:  7.6.1 
 Component:  libraries/base  |Version:  6.8.2 
Resolution:  |   Keywords:  hsetbuffering buffering buffer
Os:  Windows |   Architecture:  x86   
   Failure:  None/Unknown| Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--

Comment(by pcapriotti):

 I've spent some time looking into this. To summarize the situation:

  1. setting a console handle to unbuffered mode breaks ghci input with
 cmd.exe and cygwin
  2. unbuffered console input doesn't work properly with newline characters
 when using the POSIX API
  3. I tried the simple C program above, and it works fine, but ESC
 characters (as in the original issue) are still not detected. Maybe the
 ESC key has some special behavior? Ctrl+[ does send a '\ESC' character
 with msys, but not with cmd.exe.

 Possible solutions:

  * The best solution still seems to be to rewrite the whole IO subsystem
 using the Windows API. Is anyone working on this already, perhaps?
  * Alternatively, it might be possible to replace calls to `read` and
 `write` with `ReadFile` and `WriteFile` respectively. I think we need to
 replace both to ensure that buffering still works. The problem with this
 is that we need to carry around the windows handle, to avoid using
 `_get_osfhandle` at every call to `read`.

 I'm not sure if any of those solutions would address problem 1 above.

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


[GHC] #6044: Regression error: Kind variables don't work inside of kind constructors in type families

2012-04-25 Thread GHC
#6044: Regression error: Kind variables don't work inside of kind constructors 
in
type families
---+
 Reporter:  goldfire   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.5|   Keywords:  PolyKinds 
TypeFamilies 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+
 Many thanks for the quick bug fixes around kind variables recently.

 With the newest build (7.5.20120425), the following code fails:

 {{{
 {-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, KindSignatures #-}

 type family Foo (a :: k) :: Maybe k
 type instance Foo a = Just a
 }}}

 The error is:

 {{{
 Kind mis-match
 The first argument of `Just' should have kind `k0',
 but `a' has kind `k'
 In the type `Just a'
 In the type instance declaration for `Foo'
 }}}

 The above code compiles without error on, e.g., 7.5.20120329.

 I think it's worth noting that the following compiles fine, which
 surprised me given the error above:

 {{{
 type family Id (a :: k) :: k
 type instance Id a = a
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6044
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] #6045: GHC 6.10.4 panic when compiling she-0.6

2012-04-25 Thread GHC
#6045: GHC 6.10.4 panic when compiling she-0.6
+---
 Reporter:  nobody  |  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  6.10.4  |   Keywords:  
   Os:  MacOS X |   Architecture:  x86 
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---
 GHC says I should report, found no existing ticket (tho I regularly fail
 at searching).

 == Output ==
 {{{
 nobody@nowhere:~$ cabal install she
 Resolving dependencies...
 Configuring she-0.6...
 Preprocessing library she-0.6...
 Preprocessing executables for she-0.6...
 Building she-0.6...
 [1 of 1] Compiling ShePrelude   ( src/ShePrelude.lhs,
 dist/build/ShePrelude.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 6.10.4 for x86_64-apple-darwin):
 tcResultType/choose_univs

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

 cabal: Error: some packages failed to install:
 she-0.6 failed during the building phase. The exception was:
 ExitFailure 1
 }}}

 == System Info ==
 {{{
 nobody@nowhere:~$ uname -a
 Darwin nowhere.local 10.8.0 Darwin Kernel Version 10.8.0: Tue Jun  7
 16:33:36 PDT 2011; root:xnu-1504.15.3~1/RELEASE_I386 i386
 nobody@nowhere:~$ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 6.10.4
 }}}

 GHC installed via MacPorts.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6045
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] #6045: GHC 6.10.4 panic when compiling she-0.6

2012-04-25 Thread GHC
#6045: GHC 6.10.4 panic when compiling she-0.6
+---
 Reporter:  nobody  |  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  6.10.4  |   Keywords:  
   Os:  MacOS X |   Architecture:  x86 
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---
Changes (by nobody):

 * cc: schoepl@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6045#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] #6020: Couldn't match kind with free type variables and PolyKinds

2012-04-25 Thread GHC
#6020: Couldn't match kind with free type variables and PolyKinds
+---
  Reporter:  atnnn  |  Owner:  
  Type:  feature request| Status:  new 
  Priority:  normal |  Milestone:  
 Component:  Compiler   |Version:  7.5 
Resolution: |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  GHC rejects valid program  | Difficulty:  Unknown 
  Testcase:  polykinds/T6020|  Blockedby:  
  Blocking: |Related:  
+---
Changes (by atnnn):

  * status:  closed = new
  * resolution:  fixed =


Comment:

 If I switch to equality constraints and reverse the functional dependency
 of Id, I get the same error as above ({{{Couldn't match kind `k0' with
 `Bool'}}}):

 {{{
 {-# LANGUAGE DataKinds, FunctionalDependencies, FlexibleInstances,
  UndecidableInstances, PolyKinds, KindSignatures,
  ConstraintKinds, FlexibleContexts, GADTs #-}

 class Id (a :: k) (b :: k) | b - a
 instance a ~ b = Id a b

 class Test (x :: a) (y :: a)
 instance (Id x y, Id y z) = Test x z

 test :: Test True True = ()
 test = ()

 main = print test
 }}}

 If I comment out `main`, it loads fine but GHC now panics when I use
 `test`:

 {{{
  :load testid.hs
  test
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 7.5.20120425 for x86_64-unknown-linux):
 tcTyVarDetails k0{tv alS} [tv]
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6020#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] #6046: inconsistent type error messages between ghc and ghci

2012-04-25 Thread GHC
#6046: inconsistent type error messages between ghc and ghci
-+--
 Reporter:  carter   |  Owner:  
   
 Type:  bug  | Status:  new 
   
 Priority:  normal   |  Component:  Compiler
   
  Version:  7.5  |   Keywords:  
   
   Os:  MacOS X  |   Architecture:  x86_64 (amd64)  
   
  Failure:  Incorrect result at runtime  |   Testcase:  see problem 
description
Blockedby:   |   Blocking:  
   
  Related:   |  
-+--
 When building syb 0.3.6 with todays head / 7.5
 I get different type error messages for the module Data/Generics/Twins.hs
 respectively from ghc when doing cabal install syb vs when i load that
 module into ghci

 ghc:

 src/Data/Generics/Twins.hs:202:14:
 Illegal polymorphic or qualified type: GenericT
 Perhaps you intended to use -XRankNTypes or -XRank2Types
 In the type signature for `gzipWithT':
   gzipWithT :: GenericQ (GenericT) - GenericQ (GenericT)

 src/Data/Generics/Twins.hs:213:14:
 Illegal polymorphic or qualified type: GenericM m
 Perhaps you intended to use -XRankNTypes or -XRank2Types
 In the type signature for `gzipWithM':
   gzipWithM :: Monad m =
GenericQ (GenericM m) - GenericQ (GenericM m)

 src/Data/Generics/Twins.hs:223:14:
 Illegal polymorphic or qualified type: GenericQ r
 Perhaps you intended to use -XRankNTypes or -XRank2Types
 In the type signature for `gzipWithQ':
   gzipWithQ :: GenericQ (GenericQ r) - GenericQ (GenericQ [r])

 src/Data/Generics/Twins.hs:265:9:
 Illegal polymorphic or qualified type: GenericM Maybe
 Perhaps you intended to use -XRankNTypes or -XRank2Types
 In the type signature for `gzip':
   gzip :: GenericQ (GenericM Maybe) - GenericQ (GenericM Maybe)


 --- interestingly, rank2types is infact enabled in that module.

 whereas when the module is loaded into ghci, I get a very different error
 message

 Loading package base ... linking ... done.
 [1 of 2] Compiling Data.Generics.Aliases ( Data/Generics/Aliases.hs,
 interpreted )
 [2 of 2] Compiling Data.Generics.Twins ( Data/Generics/Twins.hs,
 interpreted )

 Data/Generics/Twins.hs:118:12: Not in scope: type variable `b'

 Data/Generics/Twins.hs:118:17: Not in scope: type variable `a'

 Data/Generics/Twins.hs:118:39: Not in scope: type variable `b'

 Data/Generics/Twins.hs:118:42: Not in scope: type variable `a'


 
 irrespective of fixing the type error (i hope to sort that out this
 evening),
 the type error message should be the same between ghc and ghci in this
 instance right?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6046
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] #6046: inconsistent type error messages between ghc and ghci

2012-04-25 Thread GHC
#6046: inconsistent type error messages between ghc and ghci
-+--
 Reporter:  carter   |  Owner:  
   
 Type:  bug  | Status:  new 
   
 Priority:  normal   |  Component:  Compiler
   
  Version:  7.5  |   Keywords:  
   
   Os:  MacOS X  |   Architecture:  x86_64 (amd64)  
   
  Failure:  Incorrect result at runtime  |   Testcase:  see problem 
description
Blockedby:   |   Blocking:  
   
  Related:   |  
-+--

Comment(by carter):

 interestingly, when I add  ScopedTypeVariables  to the language pragma,
 ghci's type error agrees with the ghc type error.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6046#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] #6046: inconsistent type error messages between ghc and ghci

2012-04-25 Thread GHC
#6046: inconsistent type error messages between ghc and ghci
-+--
 Reporter:  carter   |  Owner:  
   
 Type:  bug  | Status:  new 
   
 Priority:  normal   |  Component:  Compiler
   
  Version:  7.5  |   Keywords:  
   
   Os:  MacOS X  |   Architecture:  x86_64 (amd64)  
   
  Failure:  Incorrect result at runtime  |   Testcase:  see problem 
description
Blockedby:   |   Blocking:  
   
  Related:   |  
-+--

Comment(by carter):

 this isn't relevant to this bug, but the type error associated with the
 bug goes away if the Language pragma for Data.Generics.Twins
 is changed from Rank2Types to RankNTypes

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6046#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] #6046: inconsistent type error messages between ghc and ghci

2012-04-25 Thread GHC
#6046: inconsistent type error messages between ghc and ghci
+---
Reporter:  carter   |Owner: 

Type:  bug  |   Status:  closed 

Priority:  normal   |Component:  Compiler   

 Version:  7.5  |   Resolution:  invalid

Keywords:   |   Os:  MacOS X

Architecture:  x86_64 (amd64)   |  Failure:  Incorrect result at 
runtime
Testcase:  see problem description  |Blockedby: 

Blocking:   |  Related: 

+---
Changes (by dreixel):

  * status:  new = closed
  * resolution:  = invalid


Comment:

 The syb.cabal file (see
 http://hackage.haskell.org/packages/archive/syb/0.3.6/syb.cabal) mentions
 the extension `ScopedTypeVariables`, but if you load the file on GHCi you
 won't get this. This explains the difference in behaviour between `cabal
 install` and just loading the file on GHCi.

 The `RankNTypes` error itself is already reported as #6032. I think the
 best thing to do is to change `syb`; I'll release an updated version
 today.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6046#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] #6046: inconsistent type error messages between ghc and ghci

2012-04-25 Thread GHC
#6046: inconsistent type error messages between ghc and ghci
+---
Reporter:  carter   |Owner: 

Type:  bug  |   Status:  closed 

Priority:  normal   |Component:  Compiler   

 Version:  7.5  |   Resolution:  invalid

Keywords:   |   Os:  MacOS X

Architecture:  x86_64 (amd64)   |  Failure:  Incorrect result at 
runtime
Testcase:  see problem description  |Blockedby: 

Blocking:   |  Related: 

+---

Comment(by carter):

 that clarifies things. thanks!

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