
On Sunday 26 September 2010 14:00:38, Kevin Jardine wrote:
OK, thanks for this advice.
The type definition compiles, but when I try to actually access myField, the compiler says:
Cannot use record selector `myField' as a function due to escaped type variables Probable fix: use pattern-matching syntax instead
So I took the hint and wrote a new pattern matching accessor function:
getMyField (MyStruct value) = value
and I get:
Inferred type is less polymorphic than expected Quantified type variable `a' escapes When checking an existential match that binds value :: a
Any further suggestions?
Ah, yes, forgot about that. As GHC says, using getMyValue would let the quantified type variable escape, the type would be getMyValue :: exists a. MyStruct -> a (not allowed in Haskell). You can only use myField per pattern matching foo :: MyStruct -> whatever foo (MyStruct field) = methodOfMyTypeClass field
On Sep 26, 1:09 pm, Daniel Fischer
wrote: On Sunday 26 September 2010 12:53:46, Michael Snoyman wrote:
data MyStruct = forall a. MyTypeClass a => MyStruct {myField :: a}
Note that that requires {-# LANGUAGE ExistentialQuantification #-}