[GHC] #13684: Core lint error with defer-typed-holes and coerce
GHC
ghc-devs at haskell.org
Wed May 10 23:57:02 UTC 2017
#13684: Core lint error with defer-typed-holes and coerce
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# Options_GHC -dcore-lint -fdefer-typed-holes #-}
{-# Language FlexibleInstances, UndecidableInstances,
MultiParamTypeClasses, GeneralizedNewtypeDeriving #-}
import Data.Traversable
import Control.Lens.Indexed
import Control.Lens.Fold (ifoldMapOf)
import Control.Lens.Setter (iover)
newtype Foo a = F (WrapITraversable [] a)
newtype WrapITraversable f a = WIT (f a)
instance TraversableWithIndex i f => Functor (WrapITraversable f) where
fmap = fmapDefault
instance TraversableWithIndex i f => Foldable (WrapITraversable f) where
foldMap = foldMapDefault
instance TraversableWithIndex i f => Traversable (WrapITraversable f)
where
traverse = itraverse . const
instance TraversableWithIndex i f => FoldableWithIndex i (WrapITraversable
f) where
ifoldMap = ifoldMapOf itraversed
instance TraversableWithIndex i f => FunctorWithIndex i (WrapITraversable
f) where
imap = iover itraversed
instance TraversableWithIndex i f => TraversableWithIndex i
(WrapITraversable f) where
itraverse = coerce itraverse
}}}
causes with `lens 4.14` or `4.15.1`, GHC 8.0.1.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13684>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list