[Haskell-beginners] using record in aeson

Rick Murphy rick at rickmurphy.org
Wed Oct 19 02:23:43 CEST 2011


Thanks, David. That was great advice. 

I wonder whether you and others might provide more advice on how to
improve the worked example below. I suspect the compiler provides a hint
with the pattern match overlap warning, but I wonder what opportunities
for refactoring an experienced Haskeller would envision. 

In terms of background, the worked example partially implements the
following specification.

http://docs.api.talis.com/platform-api/output-types/rdf-json

Here's a test string and the worked example:

{"http://www.example.com/about":{"http://purl.org/dc/elements/1.1/title":{"type":"literal","value":"Rick's Home Page","lang":"http://w3.org/en","datatype":"http://w3.org/#string"},"http://purl.org/dc/elements/1.1/title":{"type":"literal","value":"Rick's Home Page","lang":"http://w3.org/en","datatype":"http://w3.org/#string"}}}

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Applicative
import Control.Monad (mzero)

import qualified Data.ByteString as B
import qualified Data.Map as M
import qualified Data.Text as T

import Data.Aeson
import qualified Data.Aeson.Types as J
import Data.Attoparsec

data RDFType = Literal T.Text | URI T.Text | BNode T.Text deriving
(Show)
type RDFValue = T.Text
type Lang = T.Text
type DTyp = T.Text

data RDFObject = RDFObject {s :: RDFType, u :: RDFValue, v :: Lang, w ::
DTyp} deriving (Show)
data Property = Property (T.Text, RDFObject) deriving (Show)
data Subject = Subject (T.Text, [Property]) deriving (Show)
data RDF       = RDF [Subject] deriving Show

instance FromJSON Subject
  where
    parseJSON (Object o) = Subject <$> toSubject o
       where
        toSubject :: (M.Map T.Text Value) -> J.Parser (T.Text,
[Property])
        toSubject o' = do

         s <- return $ M.assocs o'
         k <- return $ fst $ head s
         v <- return $ snd $ head s   

         ps <- mapM (parseJSON :: Value -> J.Parser Property) (M.elems
o')

         return $ (k,ps)

        toSubject _              = error "unexpected subject"

    parseJSON _          = mzero

instance FromJSON RDFObject where
 parseJSON (Object o) = RDFObject <$> (o .: "type") <*> (o .: "value")
<*> (o .: "lang") <*> (o .: "datatype")

instance FromJSON Property where
  parseJSON (Object o) = Property <$> toProperty o
   where
    toProperty :: (M.Map T.Text Value) -> J.Parser (T.Text, RDFObject)
    toProperty o' = do

     p <- return $ M.assocs o'
     k <- return $ fst $ head p
     v <- return $ snd $ head p
     
     o'' <- parseJSON v :: J.Parser RDFObject

     return (k,o'')
    toProperty _        = error "unexpected property"

  parseJSON _ = mzero  

instance FromJSON RDFType where
 parseJSON v@(String s) | v == "literal" = return $ Literal s
                        | v == "bnode" = return $ BNode s 
                        | otherwise = return $ URI s

parseAll :: B.ByteString -> [Subject]
parseAll s = case (parse (fromJSON <$> json) s) of
  Done _ (Error err)  -> error err
  Done ss (Success e) -> e:(parseAll ss)
  _                   -> []

main :: IO ()
main = do s <- B.readFile "6.json"
          let p = RDF $ parseAll s
          print p

--
Rick

On Wed, 2011-10-12 at 11:21 -0400, David McBride wrote:
> The problem is that in parseObject, from the moment you type 'return',
> you are then in pure code.  But you are trying to do applicative
> functions as if you are still in the Parser monad.  Here is a way to
> rewrite this.
> 
> First rewrite
> data MyRecord = MyRecord {s :: T.Text, u :: T.Text} deriving (Show)
> because we are using Text not String, then
> 
> parseObject o' = mapM toMyPair (M.assocs o')
>   where
>     toMyPair :: (T.Text, Value) -> J.Parser MyPair
>     toMyPair (t, Object o'') = do
>       rec <- MyRecord <$> (o'' .: "type") <*> (o'' .: "value") ::
> J.Parser MyRecord
>       return $ R (t, rec)
>     toMyPair _              = error "unexpected"
> 
> That is, stay in the parser monad and pull out the things you need
> using do notation, then return the whole thing back into the parser
> monad.  You could have also gone:
> 
>     toMyPair (t, Object o'') = do
>       typ <- o'' .: "type"
>       val <- o'' .: "value"
>       return $ R (t, MyRecord typ val)
> 
> 
> On Tue, Oct 11, 2011 at 9:17 PM, Rick Murphy <rick at rickmurphy.org> wrote:
> > Hi All:
> >
> > I've been elaborating on aeson examples and wondered whether someone
> > could clarify the syntax for using a record in a pair. My goal is to
> > substitute a record for the list of pairs created through the data
> > constructor O [(T.Text, Value)] in MyPair below. Reason being to embed
> > the semantics of the json file into the record. To reproduce, just
> > uncomment the lines in the source below.
> >
> > The json file structure is as follows:
> > {"outer":{"type":"literal","value":"rick"}}
> >
> > Note my naive attempt in the commented lines returns the following
> > message from ghci. 'f0 b0' doesn't give me much to go on.
> >
> > -- E1.hs:35:41:
> > --     Couldn't match expected type `MyRecord' with actual type `f0 b0'
> > --     In the expression: MyRecord <$> o'' .: "type" <*> o'' .: "value"
> > --     In the first argument of `R', namely
> > --       `(t, MyRecord <$> o'' .: "type" <*> o'' .: "value")'
> > --     In the expression: R (t, MyRecord <$> o'' .: "type" <*> o'' .:
> > "value")
> > -- Failed, modules loaded: none.
> >
> > {-# LANGUAGE OverloadedStrings #-}
> >
> > module Main where
> >
> > import Control.Applicative
> > import Control.Monad (mzero)
> >
> > import qualified Data.ByteString as B
> > import qualified Data.Map as M
> > import qualified Data.Text as T
> >
> > import Data.Aeson
> > import qualified Data.Aeson.Types as J
> > import Data.Attoparsec
> >
> > -- data MyRecord = MyRecord {s :: String, u :: String} deriving (Show)
> >
> > data MyPair = O (T.Text, [(T.Text, Value)])
> >           -- | R (T.Text, MyRecord)
> >              deriving (Show)
> >
> > data ExifObject = ExifObject [MyPair]
> >                deriving Show
> >
> > data Exif       = Exif [ExifObject]
> >                deriving Show
> >
> > instance FromJSON ExifObject
> >  where
> >    parseJSON (Object o) = ExifObject <$> parseObject o
> >      where
> >        parseObject o' = return $ map toMyPair (M.assocs o')
> >
> >        toMyPair (t, Object o'')= O (t, M.assocs o'')
> > --      toMyPair (t, Object o'')= R (t, MyRecord <$> o'' .: "type" <*>
> > o'' .: "value")
> >        toMyPair _              = error "unexpected"
> >
> >    parseJSON _          = mzero
> >
> > parseAll :: B.ByteString -> [ExifObject]
> > parseAll s = case (parse (fromJSON <$> json) s) of
> >  Done _ (Error err)  -> error err
> >  Done ss (Success e) -> e:(parseAll ss)
> >  _                   -> []
> >
> > main :: IO ()
> > main = do s <- B.readFile "e1.json"
> >          let p = Exif $ parseAll s
> >          print p
> >
> > --
> > Rick
> >
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >
> 





More information about the Beginners mailing list