Skip to content

Commit

Permalink
Start working on release notes and expanded examples.
Browse files Browse the repository at this point in the history
  • Loading branch information
bos committed Dec 1, 2011
1 parent a0cfef2 commit a83da41
Show file tree
Hide file tree
Showing 6 changed files with 153 additions and 33 deletions.
31 changes: 27 additions & 4 deletions Data/Aeson/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,18 @@

module Data.Aeson.Generic
(
fromJSON
-- * Decoding and encoding
decode
, encode
-- * Lower-level conversion functions
, fromJSON
, toJSON
) where

import Control.Applicative ((<$>))
import Control.Arrow (first)
import Control.Monad.State.Strict
import Data.Aeson.Functions
import Data.Aeson.Functions hiding (decode)
import Data.Aeson.Types hiding (FromJSON(..), ToJSON(..), fromJSON)
import Data.Attoparsec.Number (Number)
import Data.Generics
Expand All @@ -35,7 +39,11 @@ import Data.Text (Text, pack, unpack)
import Data.Text.Encoding (encodeUtf8)
import Data.Time.Clock (UTCTime)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Data.Aeson.Parser (json)
import qualified Data.Aeson.Encode as E
import qualified Data.Aeson.Functions as F
import qualified Data.Aeson.Types as T
import qualified Data.Attoparsec.Lazy as L
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import qualified Data.HashMap.Strict as H
Expand All @@ -46,6 +54,21 @@ import qualified Data.Text.Lazy as LT
import qualified Data.Traversable as T
import qualified Data.Vector as V

-- | Efficiently serialize a JSON value as a lazy 'L.ByteString'.
encode :: (Data a) => a -> L.ByteString
encode = E.encode . toJSON
{-# INLINE encode #-}

-- | Efficiently deserialize a JSON value from a lazy 'L.ByteString'.
-- If this fails due to incomplete or invalid input, 'Nothing' is
-- returned.
decode :: (Data a) => L.ByteString -> Maybe a
decode s = case L.parse json s of
L.Done _ v -> case fromJSON v of
Success a -> Just a
_ -> Nothing
_ -> Nothing

type T a = a -> Value

toJSON :: (Data a) => a -> Value
Expand Down Expand Up @@ -93,7 +116,7 @@ toJSON = toJSON_generic
| tyrep == typeOf DT.empty = remap id
| tyrep == typeOf LT.empty = remap LT.toStrict
| tyrep == typeOf "" = remap pack
| tyrep == typeOf B.empty = remap decode
| tyrep == typeOf B.empty = remap F.decode
| tyrep == typeOf L.empty = remap strict
| otherwise = modError "toJSON" $
"cannot convert map keyed by type " ++ show tyrep
Expand All @@ -104,7 +127,7 @@ toJSON = toJSON_generic
| tyrep == typeOf DT.empty = remap id
| tyrep == typeOf LT.empty = remap LT.toStrict
| tyrep == typeOf "" = remap pack
| tyrep == typeOf B.empty = remap decode
| tyrep == typeOf B.empty = remap F.decode
| tyrep == typeOf L.empty = remap strict
| otherwise = modError "toJSON" $
"cannot convert map keyed by type " ++ show tyrep
Expand Down
19 changes: 12 additions & 7 deletions aeson.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,16 @@ version: 0.4.0.0
license: BSD3
license-file: LICENSE
category: Text, Web, JSON
copyright: Copyright 2011 MailRank, Inc.
copyright: (c) 2011 Bryan O'Sullivan
(c) 2011 MailRank, Inc.
author: Bryan O'Sullivan <bos@serpentine.com>
maintainer: Bryan O'Sullivan <bos@serpentine.com>
stability: experimental
tested-with: GHC == 6.12.3
tested-with: GHC == 6.12.3, GHC == 7.0.4, GHC == 7.2.2
synopsis: Fast JSON parsing and encoding
cabal-version: >= 1.8
homepage: http://github.com/bos/aeson
bug-reports: http://github.com/bos/aeson/issues
homepage: https://github.com/bos/aeson
bug-reports: https://github.com/bos/aeson/issues
build-type: Simple
description:
A JSON parsing and encoding library optimized for ease of use
Expand All @@ -20,6 +21,9 @@ description:
To get started, see the documentation for the @Data.Aeson@ module
below.
.
For release notes, see
<https://github.com/bos/aeson/blob/master/release-notes.markdown>
.
/Note/: if you use GHCi or Template Haskell, please see the
@README@ file for important details about building this package,
and other packages that depend on it:
Expand Down Expand Up @@ -80,6 +84,7 @@ description:

extra-source-files:
README.markdown
release-notes.markdown
benchmarks/AesonEncode.hs
benchmarks/AesonParse.hs
benchmarks/JsonParse.hs
Expand All @@ -98,7 +103,7 @@ extra-source-files:
benchmarks/json-data/twitter50.json
benchmarks/json-data/twitter100.json
tests/Properties.hs
examples/Demo.hs
examples/*.hs

flag developer
description: operate in developer mode
Expand Down Expand Up @@ -170,8 +175,8 @@ test-suite tests

source-repository head
type: git
location: http://github.com/bos/aeson
location: git://github.com/bos/aeson.git

source-repository head
type: mercurial
location: http://bitbucket.org/bos/aeson
location: https://bitbucket.org/bos/aeson
38 changes: 38 additions & 0 deletions examples/Generic.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
-- This example is basically the same as in Simplest.hs, only it uses
-- GHC's builtin generics instead of explicit instances of ToJSON and
-- FromJSON.

-- This example only works with GHC 7.2 or newer, as it uses the
-- datatype-generic programming machinery introduced in 7.2.

-- We enable the DeriveGeneric language extension so that GHC can
-- automatically derive the Generic class for us.

{-# LANGUAGE DeriveGeneric #-}

{-# LANGUAGE OverloadedStrings #-}

import Data.Aeson (FromJSON, ToJSON, decode, encode)
import qualified Data.ByteString.Lazy.Char8 as BL

-- To decode or encode a value using the generic machinery, we must
-- make the type an instance of the Generic class.

import GHC.Generics (Generic)

data Coord = Coord { x :: Double, y :: Double }
deriving (Show, Generic)

-- While we still have to declare our type as instances of FromJSON
-- and ToJSON, we do *not* need to provide bodies for the instances.
-- Default versions will be supplied for us.

instance FromJSON Coord
instance ToJSON Coord

main ::IO ()
main = do
let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord
print req
let reply = Coord 123.4 20
BL.putStrLn (encode reply)
30 changes: 30 additions & 0 deletions examples/GenericSYB.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
-- This example is basically the same as in Simplest.hs, only it uses
-- SYB generics instead of explicit instances of ToJSON and FromJSON.

-- This mechanism is much slower than the newer generics mechanism
-- demonstrated in Generic.hs, but it works on versions of GHC older
-- than 7.2.

-- We enable the DeriveDataTypeable language extension so that GHC can
-- automatically derive the Typeable and Data classes for us.

{-# LANGUAGE DeriveDataTypeable #-}

{-# LANGUAGE OverloadedStrings #-}

import Data.Data (Typeable, Data)
import Data.Aeson.Generic (decode, encode)
import qualified Data.ByteString.Lazy.Char8 as BL

-- To decode or encode a value using the generic machinery, we must
-- make the type an instance of the Typeable and Data classes.

data Coord = Coord { x :: Double, y :: Double }
deriving (Show, Typeable, Data)

main ::IO ()
main = do
let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord
print req
let reply = Coord 123.4 20
BL.putStrLn (encode reply)
41 changes: 19 additions & 22 deletions examples/Simplest.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,30 @@
{-# LANGUAGE OverloadedStrings #-}

import Control.Applicative ((<$>), (<*>))
import Control.Monad (mzero)
import Control.Applicative ((<$>), (<*>), empty)
import Data.Aeson
import qualified Data.Aeson.Types as T
import Data.Attoparsec (parse, Result(..))
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.ByteString.Lazy.Char8 as BL

main ::IO ()
main = do
print $ parseFromString "{\"x\":3.0,\"y\":-1.0}"
let reply = Coord 123.4 20
putStrLn $ BSL.unpack (encode reply)
data Coord = Coord { x :: Double, y :: Double }
deriving (Show)

data Coord = Coord { x :: Double, y :: Double } deriving (Show)
-- A ToJSON instance allows us to encode a value as JSON.

instance ToJSON Coord where
toJSON (Coord xV yV) = object ["x" .= xV, "y" .= yV]
toJSON (Coord xV yV) = object [ "x" .= xV,
"y" .= yV ]

-- A FromJSON instance allows us to decode a value from JSON. This
-- should match the format used by the ToJSON instance.

instance FromJSON Coord where
parseJSON (Object v) = Coord <$>
v .: "x" <*>
v .: "y"
parseJSON _ = mzero
v .: "x" <*>
v .: "y"
parseJSON _ = empty

parseFromString :: String -> Maybe Coord
parseFromString s =
let bs = BS.pack s
in case parse json bs of
Done _rest res -> T.parseMaybe parseJSON res
_ -> Nothing
main ::IO ()
main = do
let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord
print req
let reply = Coord 123.4 20
BL.putStrLn (encode reply)
27 changes: 27 additions & 0 deletions release-notes.markdown
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
# 0.3 to 0.4

## Generics support

Aeson's support for data-type generic programming makes it possible to
use JSON encodings of most data types without writing any boilerplate
instances.

Thanks to Bas Van Dijk, aeson now supports the two major schemes for
doing datatype-generic programming:

* the newer mechanism, [built into GHC
itself](http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html)

* the older mechanism, based on SYB (for "scrap your boilerplate")

The GHC-based generics are fast and terse: in fact, they're generally
comparable in performance to hand-written `ToJSON` and `FromJSON`
instances. To see how to use GHC generics, see
[`examples/Generic.hs`](https://github.com/bos/aeson/blob/master/examples/Generic.hs).

The SYB-based generics support lives in
[Data.Aeson.Generic](http://hackage.haskell.org/packages/archive/aeson/0.4.0.0/doc/html/Data-Aeson-Generic.html),
and is provided mainly for users of GHC older than 7.2. It's far
slower (by about 10x) than the more modern generic mechanism. To see
how to use SYB generics, see
[`examples/GenericSYB.hs`](https://github.com/bos/aeson/blob/master/examples/GenericSYB.hs).

0 comments on commit a83da41

Please sign in to comment.