[GHC] #7282: polykinds error: Found `k' but expected `k'

2012-09-30 Thread GHC
#7282: polykinds error: Found `k' but expected `k'
---+
 Reporter:  HolgerReinhardt|  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  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+
 {{{
 {-# OPTIONS -XTypeFamilies -XDataKinds -XPolyKinds #-}

 class Foo (xs :: [k]) where
 type Bar xs :: *

 instance Foo '[] where
 type Bar '[] = Int
 }}}
 fails with:

 {{{
 I:\a.hs:7:5:
 Type indexes must match class instance head
 Found `k' but expected `k'
 In the type instance declaration for `Bar'
 In the instance declaration for `Foo '[]'
 }}}

 If I change the kind of xs from [k] to [*], the program is accepted.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7282
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] #7283: Specialise INLINE functions

2012-09-30 Thread GHC
#7283: Specialise INLINE functions
-+--
 Reporter:  rl   |  Owner:  
 Type:  feature request  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.7  |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 Quick summary: At the moment, INLINE means inline a function if it is
 fully applied and '''don't use its unfolding''' otherwise. I think we
 might want to change this to INLINE a function if it is fully applied and
 '''treat it as to INLINABLE''' otherwise.

 Here is a small example:

 {{{
 module T where

 f :: Num a = a - a
 {-# INLINE [1] f #-}
 f = \x - x+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1

 g :: Num a = a - a
 {-# INLINE [1] g #-}
 g x = x+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2+2

 h :: Num a = a - a
 {-# INLINABLE [1] h #-}
 h x = x+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3+3

 apply :: (a - b) - a - b
 {-# NOINLINE apply #-}
 apply f x = f x
 }}}

 {{{
 module U where

 import T

 ff :: Int - Int - Int
 ff x y = apply f x + apply f y

 gg :: Int - Int - Int
 gg x y = apply g x + apply g y

 hh :: Int - Int - Int
 hh x y = apply h x + apply h y
 }}}

 With -O2 -fno-cse (CSE does optimise this example but doesn't solve the
 problem of intermediate code bloat), GHC produces the following:

   * The RHS of `f` is duplicated since it is inlined twice - '''bad'''.
   * `g` is neither inlined nor specialised since it isn't fully applied -
 '''bad'''.
   * `h` is specialised but its RHS isn't duplicated - '''good'''.

 But of course, `h` isn't guaranteed to be inlined even if it is fully
 applied which, in the real-world examples I have in mind, is '''bad'''.

 I think `INLINE [n] f` should mean that:

   1. `f` will always be inlined if it is fully applied,
   2. `f` will be specialised when possible,
   3. specialisations of `f` will also be `INLINE [n]`.

 I don't think it's possible to achieve this effect at the moment. If we
 treated `INLINE [n]` as `INLINABLE [n]` until the function is fully
 applied, we would get exactly this, though, except for 3 which probably
 isn't too hard to implement.

 Now, if I understand correctly, INLINABLE also means that GHC is free to
 inline the function if it wants but the function isn't treated as cheap. I
 think it would be fine if we did this for unsaturated `INLINE` functions
 rather than not inlining them under any circumstances. The original
 motivation for only inlining when fully applied was code bloat in DPH. But
 IIRC that only happened because INLINE functions were always cheap and so
 GHC was very keen to inline them even when they weren't saturated which
 wouldn't be the case with my proposal. We would have to check how this
 affects DPH and related libraries, though.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7283
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] #7284: plusAddr# x 0 isn't optimised away

2012-09-30 Thread GHC
#7284: plusAddr# x 0 isn't optimised away
-+--
 Reporter:  rl   |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.6.1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 As the title says, there doesn't seem to be an optimisation rule for this.
 I'm not sure if adding one to base (where exactly?) would be enough or if
 it should be a built-in one.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7284
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] #6004: dph-lifted-vseg package doesn't provide Data.Array.Parallel.Prelude.Float module

2012-09-30 Thread GHC
#6004: dph-lifted-vseg package doesn't provide Data.Array.Parallel.Prelude.Float
module
--+-
Reporter:  shelarcy   |   Owner:  benl
Type:  bug|  Status:  new 
Priority:  normal |   Milestone:  7.8.1   
   Component:  Data Parallel Haskell  | Version:  7.4.1   
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by benl):

 Just use Doubles for now. DPH is still experimental, and you probably
 won't see a performance difference between Floats and Doubles.

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