[Haskell-cafe] Impredicative types and Lens?
Artyom Kazak
yom at artyom.me
Sun Sep 8 15:49:37 CEST 2013
Here’s a small example, which, when compiled, gives an error. Why?
{-# LANGUAGE FlexibleInstances, ImpredicativeTypes,
TemplateHaskell #-}
import Control.Lens
class Item a where
name :: a -> String
instance Item (String, Int) where
name = fst
type ItemFilter = Item a => a -> Bool
data ItemBox = ItemBox { _itemFilter :: ItemFilter }
makeLenses ''ItemBox
The error is
Couldn't match type `a0 -> Bool'
with `forall a. Item a => a -> Bool'
Expected type: ItemFilter
Actual type: a0 -> Bool
In the expression: b_aaZE
In the first argument of `iso', namely
`\ (ItemBox b_aaZE) -> b_aaZE'
In the expression: iso (\ (ItemBox b_aaZE) -> b_aaZE) ItemBox
I’m using GHC 7.6.2, if it’s important.
More information about the Haskell-Cafe
mailing list