[Haskell-beginners] Fwd: Can i define a record without defining access method.

David McBride dmcbride at neondsl.com
Sat Jul 9 19:52:19 CEST 2011


I've never used the main aeson library, but I just tried the aeson-qq
library and got this without any real problem.  Try this:

{-# LANGUAGE QuasiQuotes, TemplateHaskell, DeriveDataTypeable #-}
import Data.Text
import Data.Aeson
import Data.Aeson.QQ
import Data.Aeson.Generic
import Data.Aeson.Types

myReq = [aesonQQ| {age: <|age|>, version: <|version|>} |]
 where age = 34 :: Integer
       version = "1.2"

myResp = [aesonQQ| {age: <|name|>, version: <|version|>} |]
 where name = "harold"
       version = "1.3"

>encode $ Data.Aeson.Generic.toJSON myReq
Chunk "{\"age\":34,\"version\":\"1.2\"}" Empty
>encode $ Data.Aeson.Generic.toJSON myResp
Chunk "{\"age\":\"harold\",\"version\":\"1.3\"}" Empty


On Sat, Jul 9, 2011 at 12:41 PM, yi huang <yi.codeplayer at gmail.com> wrote:
> On Sun, Jul 10, 2011 at 12:25 AM, Chaddaï Fouché <chaddai.fouche at gmail.com>
> wrote:
>>
>> On Sat, Jul 9, 2011 at 5:59 PM, yi huang <yi.codeplayer at gmail.com> wrote:
>> >  On Sat, Jul 9, 2011 at 6:45 PM, Tom Murphy <amindfv at gmail.com> wrote:
>> >>
>> >> On 7/9/11, yi huang <yi.codeplayer at gmail.com> wrote:
>> >> > I'm trying to create a haskell implementation of json rpc, I try to
>> >> > define
>> >> > protocol using record like this:
>> >> >
>> >> > data Request = Request {
>> >> >     version :: Integer
>> >> >   , id      :: Integer
>> >> >   , method  :: String
>> >> >   , args    :: [Value]
>> >> > } deriving (Typeable, Data, Show)
>> >>
>> >> > so i can use json library to encode/decode it.
>> >> > But this code fails, because haskell will define access function
>> >> > automaticlly, and function names conflicts.
>> >> > My question is, is there a way i can define record without access
>> >> > function,
>> >> > so i can have same attribute name in multiple record.
>> >>
>>
>> If you really want to keep those attribute names exactly, you'll have
>> to check where the conflict is and find a way not to import the
>> conflicting function name. Here I guess "id" is the big problem since
>> it comes with the prelude you'll have to use the NoImplicitPrelude
>> extension and explicitly "import Prelude hiding (id)", I suggest you
>> make a separate module for your type definition so you don't have to
>> worry about that in the rest of your code.
>
> Sorry i don't describe my problem well, actually i have two records, Request
> and Response, some attributes have same names, e.g. version, id.
> data Request = Request {
>     version :: Int
>     ...
> }
> data Response = Response {
>     version :: Int
>     ...
> }
> And yes, i really want to keep those names exactly, so aeson can
> automatically encode them to right json object.
> If there are no way to hide access function, then i guess i have to define
> them in seperate module, or define them as normal data constructor with
> encode/decode precedure defined manually. Both is not pleasant to me.
>>
>> --
>> Jedaï
>
>
>
> --
> http://www.yi-programmer.com/blog/
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>



More information about the Beginners mailing list