[Haskell-cafe] Re: Polymorphic record field?

Michael Snoyman michael at snoyman.com
Sun Sep 26 08:26:48 EDT 2010


How about

f myS@(MyStruct { myField = value })

?

On Sun, Sep 26, 2010 at 2:14 PM, Kevin Jardine <kevinjardine at gmail.com> wrote:
> OK, I have a solution. Ugly, but it compiles.
>
> MyStruct actually has quite a few fields but I only need to access the
> polymorphic field 4 times.
>
> So for the functions that needed that I wrote:
>
> f myS@(MyStruct value _ _ _ )
>
> and then could use value. I could then use the usual record accessors
> on myS to get the other (non-polymorphic) data.
>
> I guess that is what GHC was hinting at when it suggested pattern
> matching.
>
> That is, pattern matching could extract a value that no functions are
> apparently allowed to touch.
>
> All head spinning to me.
>
> Thanks for the (as always) fast and useful advice!
>
> Kevin
>
> On Sep 26, 2:00 pm, Kevin Jardine <kevinjard... at gmail.com> 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?
>>
>> On Sep 26, 1:09 pm, Daniel Fischer <daniel.is.fisc... at web.de> 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 #-}
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list