[GHC] #14732: -fdefer-type-holes breaks a correct program

GHC ghc-devs at haskell.org
Sun Jan 28 06:01:14 UTC 2018


#14732: -fdefer-type-holes breaks a correct program
-------------------------------------+-------------------------------------
        Reporter:  MitchellSalad     |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by MitchellSalad:

Old description:

> Here's a bug I discovered in `vector` that Ryan Scott identified as a
> regression from 7.10.3:
>
> https://github.com/haskell/vector/issues/200
>
> Here is Ryan's minimal example:
>
> {{{#!hs
>
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE KindSignatures #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> module Bug where
>
> import Prelude hiding (zip, zipWith)
>
> zipWith :: (a -> b -> c)
>         -> Bundle v a
>         -> Bundle v b
>         -> Bundle v c
> zipWith = undefined
>
> class GVector (v :: * -> *) a
> instance GVector Vector a
>
> data Bundle (v :: * -> *) a
> data Vector a
> class Unbox a
>
> stream :: GVector v a => v a -> Bundle v a
> {-# INLINE [1] stream #-}
> stream = undefined
>
> zip :: (Unbox a, Unbox b) => Vector a -> Vector b -> Vector (a, b)
> {-# INLINE [1] zip #-}
> zip = undefined
> {-# RULES "stream/zip [Vector.Unboxed]" forall as bs .
>   stream (zip as bs) = zipWith (,) (stream as)
>                                    (stream bs)   #-}{#!hs
>
> }}}
>
> Output (8.2.2):
>
> {{{
> Bug.hs:29:11: error:
>     • Could not deduce (Unbox a) arising from a use of ‘zip’
>       from the context: GVector Vector (a, b)
>         bound by the RULE "stream/zip [Vector.Unboxed]"
>         at Bug.hs:(28,11)-(30,46)
>       Possible fix:
>         add (Unbox a) to the context of
>           the RULE "stream/zip [Vector.Unboxed]"
>     • In the first argument of ‘stream’, namely ‘(zip as bs)’
>       In the expression: stream (zip as bs)
>       When checking the transformation rule "stream/zip [Vector.Unboxed]"
>    |
> 29 |   stream (zip as bs) = zipWith (,) (stream as)
>    |           ^^^^^^^^^
> }}}
>
> Similar output in 8.0.1, 8.0.2, 8.2.1

New description:

 Here's a bug I discovered in `vector` that Ryan Scott identified as a
 regression from 7.10.3:

 https://github.com/haskell/vector/issues/200

 Here is Ryan's minimal example:

 {{{#!hs

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 module Bug where

 import Prelude hiding (zip, zipWith)

 zipWith :: (a -> b -> c)
         -> Bundle v a
         -> Bundle v b
         -> Bundle v c
 zipWith = undefined

 class GVector (v :: * -> *) a
 instance GVector Vector a

 data Bundle (v :: * -> *) a
 data Vector a
 class Unbox a

 stream :: GVector v a => v a -> Bundle v a
 {-# INLINE [1] stream #-}
 stream = undefined

 zip :: (Unbox a, Unbox b) => Vector a -> Vector b -> Vector (a, b)
 {-# INLINE [1] zip #-}
 zip = undefined
 {-# RULES "stream/zip [Vector.Unboxed]" forall as bs .
   stream (zip as bs) = zipWith (,) (stream as)
                                    (stream bs)   #-}

 }}}

 Output (8.2.2):

 {{{
 Bug.hs:29:11: error:
     • Could not deduce (Unbox a) arising from a use of ‘zip’
       from the context: GVector Vector (a, b)
         bound by the RULE "stream/zip [Vector.Unboxed]"
         at Bug.hs:(28,11)-(30,46)
       Possible fix:
         add (Unbox a) to the context of
           the RULE "stream/zip [Vector.Unboxed]"
     • In the first argument of ‘stream’, namely ‘(zip as bs)’
       In the expression: stream (zip as bs)
       When checking the transformation rule "stream/zip [Vector.Unboxed]"
    |
 29 |   stream (zip as bs) = zipWith (,) (stream as)
    |           ^^^^^^^^^
 }}}

 Similar output in 8.0.1, 8.0.2, 8.2.1

--

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14732#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list