{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP #-}
module Network.Riak.JSON
(
JSON
, json
, plain
, get
, getMany
, put
, putIndexed
, put_
, putMany
, putMany_
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
import Control.Arrow (first)
import Data.Aeson.Types (FromJSON(..), ToJSON(..))
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (Monoid)
#endif
import Data.Semigroup (Semigroup)
import Data.Typeable (Typeable)
import Network.Riak.Types.Internal
import qualified Network.Riak.Value as V
newtype JSON a = J {
plain :: a
} deriving (Eq, Ord, Show, Read, Bounded, Typeable, Semigroup, Monoid)
json :: a -> JSON a
json = J
{-# INLINE json #-}
instance Functor JSON where
fmap f (J a) = J (f a)
{-# INLINE fmap #-}
instance (FromJSON a, ToJSON a) => V.IsContent (JSON a) where
parseContent c = J `fmap` (V.parseContent c >>= parseJSON)
{-# INLINE parseContent #-}
toContent (J a) = V.toContent (toJSON a)
{-# INLINE toContent #-}
get :: (FromJSON c, ToJSON c) => Connection
-> Maybe BucketType -> Bucket -> Key -> R
-> IO (Maybe ([c], VClock))
get conn btype bucket' key' r = fmap convert <$> V.get conn btype bucket' key' r
getMany :: (FromJSON c, ToJSON c) => Connection
-> Maybe BucketType -> Bucket -> [Key] -> R
-> IO [Maybe ([c], VClock)]
getMany conn btype bucket' ks r = map (fmap convert) <$> V.getMany conn btype bucket' ks r
put :: (FromJSON c, ToJSON c) =>
Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c
-> W -> DW -> IO ([c], VClock)
put conn btype bucket' key' mvclock val w dw =
convert <$> V.put conn btype bucket' key' mvclock (json val) w dw
putIndexed :: (FromJSON c, ToJSON c)
=> Connection -> Maybe BucketType -> Bucket -> Key -> [IndexValue]
-> Maybe VClock -> c
-> W -> DW -> IO ([c], VClock)
putIndexed conn btype bucket' key' ixs mvclock val w dw =
convert <$> V.putIndexed conn btype bucket' key' ixs mvclock (json val) w dw
put_ :: (FromJSON c, ToJSON c) =>
Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c
-> W -> DW -> IO ()
put_ conn btype bucket' key' mvclock val w dw =
V.put_ conn btype bucket' key' mvclock (json val) w dw
putMany :: (FromJSON c, ToJSON c) =>
Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)]
-> W -> DW -> IO [([c], VClock)]
putMany conn btype bucket' puts w dw =
map convert <$> V.putMany conn btype bucket' (map f puts) w dw
where f (k,v,c) = (k,v,json c)
putMany_ :: (FromJSON c, ToJSON c) =>
Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)]
-> W -> DW -> IO ()
putMany_ conn btype bucket' puts w dw = V.putMany_ conn btype bucket' (map f puts) w dw
where f (k,v,c) = (k,v,json c)
convert :: ([JSON a], VClock) -> ([a], VClock)
convert = first (map plain)