Re: [GHC] #3990: UNPACK doesn't unbox data families

2012-12-24 Thread GHC
#3990: UNPACK doesn't unbox data families
-+--
Reporter:  rl|   Owner: 
Type:  bug   |  Status:  new
Priority:  low   |   Milestone:  7.6.2  
   Component:  Compiler  | Version:  7.0.3  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:|Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by simonpj@…):

 commit 1ee1cd4194555e498d05bfc391b7b0e635d11e29
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Sun Dec 23 15:38:48 2012 +

 Make {-# UNPACK #-} work for type/data family invocations

 This fixes most of Trac #3990.  Consider
   data family D a
   data instance D Double = CD Int Int
   data T = T {-# UNPACK #-} !(D Double)
 Then we want the (D Double unpacked).

 To do this we need to construct a suitable coercion, and it's much
 safer to record that coercion in the interface file, lest the in-scope
 instances differ somehow.  That in turn means elaborating the HsBang
 type to include a coercion.

 To do that I moved HsBang from BasicTypes to DataCon, which caused
 quite a few minor knock-on changes.

 Interface-file format has changed!

 Still to do: need to do knot-tying to allow instances to take effect
 within the same module.

  compiler/basicTypes/BasicTypes.lhs |   51 --
  compiler/basicTypes/DataCon.lhs|   52 ++-
  compiler/basicTypes/MkId.lhs   |  230
 ++--
  compiler/hsSyn/HsTypes.lhs |1 +
  compiler/iface/BinIface.hs |   20 +--
  compiler/iface/BuildTyCl.lhs   |   12 +-
  compiler/iface/IfaceSyn.lhs|   13 +-
  compiler/iface/MkIface.lhs |8 +-
  compiler/iface/TcIface.lhs |   13 ++-
  compiler/main/PprTyThing.hs|3 +-
  compiler/prelude/TysWiredIn.lhs|2 +-
  compiler/simplCore/Simplify.lhs|4 +-
  compiler/stranal/DmdAnal.lhs   |4 +-
  compiler/typecheck/TcRnDriver.lhs  |2 +-
  compiler/typecheck/TcSplice.lhs|   10 +-
  compiler/typecheck/TcTyClsDecls.lhs|6 +-
  compiler/vectorise/Vectorise/Generic/PData.hs  |9 +-
  compiler/vectorise/Vectorise/Type/TyConDecl.hs |4 +-
  18 files changed, 253 insertions(+), 191 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3990#comment:13
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] #7525: Compiler panic with ill-typed code using implicit parameters

2012-12-24 Thread GHC
#7525: Compiler panic with ill-typed code using implicit parameters
---+
Reporter:  parcs   |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Compiler
 Version:  7.7 |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by simonpj@…):

 commit 1d07cc04ebcaa2df69824aeb1406557946e6dd19
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Mon Dec 24 09:46:55 2012 +

 Remember to zonk when taking free variables in simpl_top

 Forgetting this meant that we were upating the same
 meta-tyvar twice.  Fixes Trac #7525.

  compiler/typecheck/TcSMonad.lhs   |4 
  compiler/typecheck/TcSimplify.lhs |   24 
  2 files changed, 16 insertions(+), 12 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7525#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] #7258: Compiling DynFlags is jolly slow

2012-12-24 Thread GHC
#7258: Compiling DynFlags is jolly slow
-+--
Reporter:  simonpj   |   Owner:  simonpj 
Type:  bug   |  Status:  new 
Priority:  normal|   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:|  
-+--

Comment(by simonpj@…):

 commit 52e43004f63276c1342933e40a673ad25cf2113a
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Fri Dec 21 17:39:33 2012 +

 Use expectP in deriving( Read )

 Note [Use expectP]   in TcGenDeriv
 ~~
 Note that we use
expectP (Ident T1)
 rather than
Ident T1 - lexP
 The latter desugares to inline code for matching the Ident and the
 string, and this can be very voluminous. The former is much more
 compact.  Cf Trac #7258, although that also concerned non-linearity in
 the occurrence analyser, a separate issue.

  compiler/prelude/PrelNames.lhs|3 +-
  compiler/typecheck/TcGenDeriv.lhs |   43
 ++--
  2 files changed, 28 insertions(+), 18 deletions(-)
 }}}

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

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)?

2012-12-24 Thread GHC
#7450: Regression in optimisation time of functions with many patterns (6.12 to
7.4)?
---+
  Reporter:  iustin|  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Compile-time performance bug  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj):

 One reason that the derived code was big was this. The derived `Read` code
 has lots of this
 {{{
do { ...
   ; Ident foo - lexP
   ; Punc = - lexP
   ;  ...
 }}}
 Each of these failable pattern matches generates a case expression with a
 call to `error` and an error string.  This is very wasteful.  Better
 instead to define in `GHC.Read`:
 {{{
   expectP :: L.Lexeme - ReadPrec ()
 }}}
 and use it thus
 {{{
do { ...
   ; expectP (Ident foo)
   ; expectP (Punc =)
   ;  ...
 }}}
 This makes the code significantly shorter.  Without -O, and 200
 constructors, the compiler itself allocates half as much as before.

 This may or may not address the non-linearity, but it certainly improves
 `Read` instances.
 {{{
 commit 52e43004f63276c1342933e40a673ad25cf2113a
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Fri Dec 21 17:39:33 2012 +

 Use expectP in deriving( Read )

 Note [Use expectP]   in TcGenDeriv
 ~~
 Note that we use
expectP (Ident T1)
 rather than
Ident T1 - lexP
 The latter desugares to inline code for matching the Ident and the
 string, and this can be very voluminous. The former is much more
 compact.  Cf Trac #7258, although that also concerned non-linearity in
 the occurrence analyser, a separate issue.
 }}}
 There is an accompanying patch to `base`:
 {{{
 commit d9b6b25a30bfdaefb69c29dedb30eed06ae71e61
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Fri Dec 21 17:40:08 2012 +

 Define GHC.Read.expectP and Text.Read.Lex.expect

 They are now used by TcGenDeriv

 ---

  GHC/Read.lhs |   29 -
  Text/Read/Lex.hs |7 ++-
  2 files changed, 22 insertions(+), 14 deletions(-)

 diff --git a/GHC/Read.lhs b/GHC/Read.lhs index c5024fc..c542274 100644
 --- a/GHC/Read.lhs
 +++ b/GHC/Read.lhs
 @@ -32,7 +32,7 @@ module GHC.Read
, lexDigits

-- defining readers
 -  , lexP
 +  , lexP, expectP
, paren
, parens
, list
 @@ -270,12 +270,15 @@ lexP :: ReadPrec L.Lexeme
  -- ^ Parse a single lexeme
  lexP = lift L.lex

 +expectP :: L.Lexeme - ReadPrec ()
 +expectP lexeme = lift (L.expect lexeme)
 +
  paren :: ReadPrec a - ReadPrec a
  -- ^ @(paren p)@ parses \(P0)\
  --  where @p@ parses \P0\ in precedence context zero
 -paren p = do L.Punc ( - lexP
 - x  - reset p
 - L.Punc ) - lexP
 +paren p = do expectP (L.Punc ()
 + x - reset p
 + expectP (L.Punc ))
   return x

  parens :: ReadPrec a - ReadPrec a
 @@ -292,7 +295,7 @@ list :: ReadPrec a - ReadPrec [a]
  -- using the usual square-bracket syntax.
  list readx =
parens
 -  ( do L.Punc [ - lexP
 +  ( do expectP (L.Punc [)
 (listRest False +++ listNext)
)
   where
 @@ -408,12 +411,12 @@ parenthesis-like objects such as (...) and [...] can
 be an argument to  instance Read a = Read (Maybe a) where
readPrec =
  parens
 -(do L.Ident Nothing - lexP
 +(do expectP (L.Ident Nothing)
  return Nothing
   +++
   prec appPrec (
 -do L.Ident Just - lexP
 -   x  - step readPrec
 +do expectP (L.Ident Just)
 +   x - step readPrec
 return (Just x))
  )

 @@ -427,7 +430,7 @@ instance Read a = Read [a] where

  instance  (Ix a, Read a, Read b) = Read (Array a b)  where
  readPrec = parens $ prec appPrec $
 -   do L.Ident array - lexP
 +   do expectP (L.Ident array)
theBounds - step readPrec
vals   - step readPrec
return (array theBounds vals) @@ -504,9 +507,9 @@
 instance (Integral a, Read a) = Read (Ratio a) where
readPrec =
  parens
  ( prec ratioPrec
 -  ( do x- step readPrec
 -   L.Symbol % - lexP
 -   y- step readPrec
 +  ( do x - step readPrec
 +

Re: [GHC] #7525: Compiler panic with ill-typed code using implicit parameters

2012-12-24 Thread GHC
#7525: Compiler panic with ill-typed code using implicit parameters
-+--
Reporter:  parcs |   Owner: 
Type:  bug   |  Status:  merge  
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.7
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash 
  Difficulty:  Unknown   |Testcase:  typecheck/should_fail/T7525
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * status:  new = merge
  * difficulty:  = Unknown
  * testcase:  = typecheck/should_fail/T7525


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7525#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] #7507: loop fusion not working for Int32, Int64 as it does for Int ?

2012-12-24 Thread GHC
#7507: loop fusion not working for Int32, Int64 as it does for Int ?
+---
  Reporter:  j.waldmann |  Owner:
  Type:  bug| Status:  closed
  Priority:  normal |  Milestone:
 Component:  Compiler   |Version:  7.6.1 
Resolution:  fixed  |   Keywords:
Os:  Linux  |   Architecture:  x86_64 (amd64)
   Failure:  None/Unknown   | Difficulty:  Unknown   
  Testcase:  perf/should_run/T7507  |  Blockedby:
  Blocking: |Related:
+---
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed
  * testcase:  = perf/should_run/T7507


Comment:

 See also #4321.  Fixed by this patch to `base`:
 {{{
 commit 06e36c63fce9aef5d3d8d9efeab1426d48bf
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Mon Dec 24 14:44:31 2012 +

 Make sum and product INLINABLE

 This was causing the bad behaviour in Trac #7507,
 because 'sum' wasn't getting specialised to Int64.

 It also deals with Trac #4321, which had the same cause.

 This has a big effect on some nofib programs too:

 

 Program   Allocs   Runtime   Elapsed  TotalMem
 
  bernouilli-2.6% -2.0% -2.0% +0.0%
fft2   -23.8%  0.09  0.09-16.7%
   fluid-4.4%  0.01  0.01 +0.0%
  hidden-3.2% +2.1% +1.8% +0.0%
   integrate   -38.0%-47.7%-47.7% -1.0%
x2n1   -30.2%  0.01  0.01-50.0%
 
 Min   -38.0%-47.7%-47.7%-50.0%
 Max+0.4%+11.2%+11.8% +6.9%
  Geometric Mean-1.3% +0.2% +0.2% -0.8%

  Data/List.hs |5 +
  1 file changed, 5 insertions(+)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7507#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] #4321: Unexpected stack overflow prevented by superfluous type annotation

2012-12-24 Thread GHC
#4321: Unexpected stack overflow prevented by superfluous type annotation
---+
  Reporter:  bjpop |  Owner:  simonpj 
  Type:  bug   | Status:  closed  
  Priority:  high  |  Milestone:  7.6.2   
 Component:  Compiler  |Version:  7.5 
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  T4321 |  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 In the end, the patch to #7507 fixed this too.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4321#comment:21
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] #7526: Minor typo in error message

2012-12-24 Thread GHC
#7526: Minor typo in error message
-+--
Reporter:  parcs |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 Compiling the following snippet

 {{{
 {-# LANGUAGE MultiParamTypeClasses #-}
 class A a b

 class B a
 instance (A a b) = B ()
 }}}

 gives the following error message

 {{{
 [1 of 1] Compiling Main ( nomore.hs, nomore.o )

 nomore.hs:5:10:
 Variable s `a, b' occur more often than in the instance head
   in the constraint: A a b
 (Use -XUndecidableInstances to permit this)
 In the instance declaration for `B ()'
 }}}

 Note that Variable and s are erroneously separated by a space.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7526
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] #7527: Couldn't match kind `*' with `*' with PolyKinds GADTs.

2012-12-24 Thread GHC
#7527: Couldn't match kind `*' with `*' with PolyKinds  GADTs.
--+-
Reporter:  Ashley Yakeley |  Owner: 
Type:  bug| Status:  new
Priority:  normal |  Component:  Compiler (Type checker)
 Version:  7.6.1  |   Keywords: 
  Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple   
 Failure:  GHC rejects valid program  |  Blockedby: 
Blocking: |Related: 
--+-
 {{{
 {-# LANGUAGE ExistentialQuantification, DataKinds, PolyKinds,
 KindSignatures, GADTs #-}
 module TestKindMatching where
 import GHC.Exts hiding (Any)

 data WrappedType = forall a. WrapType a

 data T (wt :: WrappedType)

 class P (p :: WrappedType - *) where
  get :: T wt - p wt

 data W :: (k - *) - WrappedType - * where
 MkW :: forall (f :: k - *) (a :: k). (f a) - W f (WrapType a)

 instance P (W (f :: * - *)) where
 get = get

 thing :: forall (a :: *) (f :: * - *). T (WrapType a) - f a
 thing t = case (get t) of
 MkW cw - cw
 }}}

 {{{
 $ ghc -c TestKindMatching.hs

 TestKindMatching.hs:20:9:
 Couldn't match kind `*' with `*'
 Expected type: a1
   Actual type: a
 Kind incompatibility when matching types:
   a :: *
   a1 :: *
 In the pattern: MkW cw
 In a case alternative: MkW cw - cw
 }}}

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