[GHC] #14488: Can't define a lens for a field with a constraint
GHC
ghc-devs at haskell.org
Mon Nov 20 05:42:12 UTC 2017
#14488: Can't define a lens for a field with a constraint
-------------------------------------+-------------------------------------
Reporter: int-index | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE RankNTypes #-}
type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s
data T a = MkT { _tfield :: Eq a => a }
tfield :: Eq a => Lens' (T a) a
tfield f t = MkT <$> f (_tfield t)
}}}
This code compiles with GHC 8.2.1.
On GHC 8.0.2 the following error is reported:
{{{#!hs
tfield.hs:8:22: error:
• Couldn't match type ‘a’ with ‘Eq a => a’
‘a’ is a rigid type variable bound by
the type signature for:
tfield :: forall a. Eq a => Lens' (T a) a
at tfield.hs:7:11
Expected type: f (Eq a => a)
Actual type: f a
• In the second argument of ‘(<$>)’, namely ‘f (_tfield t)’
In the expression: MkT <$> f (_tfield t)
In an equation for ‘tfield’: tfield f t = MkT <$> f (_tfield t)
• Relevant bindings include
t :: T a (bound at tfield.hs:8:10)
f :: a -> f a (bound at tfield.hs:8:8)
tfield :: Lens' (T a) a (bound at tfield.hs:8:1)
}}}
I could not find a relevant GHC ticket. Unless it's a known issue, I am
going to create a Phab Diff with this code as a test case to avoid a
regression in the future.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14488>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list