[Haskell-cafe] Fwd: How to make this data type work?

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Mon Jun 24 03:49:15 CEST 2013


Thank you guys.

I cannot use a explicit type for there are quite a few of them. But from
MigMit, I understand why my original cannot work.


On Sat, Jun 22, 2013 at 4:46 AM, Vincent Ambo <tazjin at gmail.com> wrote:

> Is there a reason why you can't use an explicit type variable?
>
> {-# LANGUAGE OverloadedStrings, ExistentialQuantification #-}
>
> import Data.Aeson
> import Control.Applicative
> import Control.Monad (mzero)
>
> data ActionData j
> = (FromJSON j, ToJSON j) => AD j j
>
> instance ToJSON (ActionData j) where
>   toJSON (AD o n) = object [ "oldData" .= o
>                            , "newData" .= n ]
>
> instance (ToJSON j, FromJSON j) => FromJSON (ActionData j) where
>   parseJSON (Object v) = AD
>     <$> v .: "oldData"
>     <*> v .: "newData"
>   parseJSON _ = mzero
>
>
> 2013/6/21 Miguel Mitrofanov <miguelimo38 at yandex.ru>
>
>> Forgot to reply all, as usual.
>>
>> -------- Пересылаемое сообщение  --------
>> 21.06.2013, 12:52, "Miguel Mitrofanov" <miguelimo38 at yandex.ru>:
>>
>> Actually, this is not the real error you should care about. Try removing
>> FromJSON instance completely, and you'll get a lot more. And these are
>> fundamental: you have to decide what "j" to use when serializing. Haskell
>> won't automagically substitute some suitable type for you.
>>
>> So, that's a classic mismatch: for serializing (ToJSON) you need your "j"
>> type to be known to the AD value (meaning: it should be quantified
>> existentially), but for deserializing you need it to be any type
>> (quantified universally).
>>
>> All in all, AD seems to be the wrong type.
>>
>> 21.06.2013, 12:18, "Magicloud Magiclouds" <magicloud.magiclouds at gmail.com
>> >:
>>
>> >  data ActionData = AD { oldData :: (FromJSON j, ToJSON j) => j
>> >                       , newData :: (FromJSON j, ToJSON j) => j}
>> >  instance ToJSON ActionData where
>> >    toJSON (AD o n) = object [ "oldData" .= o
>> >                             , "newData" .= n ]
>> >  instance FromJSON ActionData where
>> >    parseJSON (Object v) = AD
>> >      <$> v .: "oldData"
>> >      <*> v .: "newData"
>> >    parseJSON _ = mzero
>> >
>> >  I got when compile:
>> >      No instance for (FromJSON (forall j. (FromJSON j, ToJSON j) => j))
>> >        arising from a use of `.:'
>> >      Possible fix:
>> >        add an instance declaration for
>> >        (FromJSON (forall j. (FromJSON j, ToJSON j) => j))
>> >      In the second argument of `(<$>)', namely `v .: "oldData"'
>> >      In the first argument of `(<*>)', namely `AD <$> v .: "oldData"'
>> >      In the expression: AD <$> v .: "oldData" <*> v .: "newData"
>> >
>> >  --
>> >  竹密岂妨流水过
>> >  山高哪阻野云飞
>> >
>> >  And for G+, please use magiclouds#gmail.com.
>> >  ,
>> >  _______________________________________________
>> >  Haskell-Cafe mailing list
>> >  Haskell-Cafe at haskell.org
>> >  http://www.haskell.org/mailman/listinfo/haskell-cafe
>> -------- Завершение пересылаемого сообщения --------
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130624/1c204a10/attachment.htm>


More information about the Haskell-Cafe mailing list