| Copyright | (c) Scrive 2011 |
|---|---|
| License | BSD-style (see the LICENSE file in the distribution) |
| Maintainer | mariusz@scrive.com |
| Stability | development |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
Text.JSON.FromJSValue
Description
Interface for extracting data from JSValue.
- class FromJSValue a where
- fromJSValue :: JSValue -> Maybe a
- fromJSValueM :: MonadReader JSValue m => m (Maybe a)
- class FromJSValueWithUpdate a where
- fromJSValueWithUpdate :: Maybe a -> JSValue -> Maybe a
- fromJSValueWithUpdateM :: MonadReader JSValue m => Maybe a -> m (Maybe a)
- class MatchWithJSValue a where
- matchesWithJSValue :: a -> JSValue -> Bool
- matchesWithJSValueM :: MonadReader JSValue m => a -> m Bool
- jsValueField :: (MonadReader JSValue m, FromJSValue a) => String -> m (Maybe (Maybe a))
- fromJSValueField :: (MonadReader JSValue m, FromJSValue a) => String -> m (Maybe a)
- fromJSValueFieldBase64 :: MonadReader JSValue m => String -> m (Maybe ByteString)
- fromJSValueFieldCustom :: MonadReader JSValue m => String -> m (Maybe a) -> m (Maybe a)
- fromJSValueCustomMany :: MonadReader JSValue m => m (Maybe a) -> m (Maybe [a])
- fromJSValueCustomList :: MonadReader JSValue m => [m (Maybe a)] -> m (Maybe [a])
- fromJSValueManyWithUpdate :: (MonadReader JSValue m, FromJSValueWithUpdate a, MatchWithJSValue a) => [a] -> m (Maybe [a])
- withJSValue :: Monad m => JSValue -> ReaderT JSValue m a -> m a
Basic Parsing
class FromJSValue a where Source
Structures that can be parsed from JSON. Instances must declare
either fromJSValue (parse directly from JSValue) or
fromJSValueM (uses MonadReader).
Example implementation:
data D = D String Int
instance FromJSValue D where
fromJSValue = do
s <- fromJSValueField "string_key"
i <- fromJSValueField "int_key"
return (D <$> s <*> i)Note that we make use of MonadReader instance for "(->)" and of
Applicative programming style with <$> and <*>.
Note: fromJSValueM is deprecated, in future fromJSValue will be
generalized to work in any MonadReader JSValue.
Minimal complete definition
Nothing
Methods
fromJSValue :: JSValue -> Maybe a Source
fromJSValueM :: MonadReader JSValue m => m (Maybe a) Source
Instances
| FromJSValue Bool Source | |
| FromJSValue Double Source | |
| FromJSValue Float Source | |
| FromJSValue Int Source | |
| FromJSValue Int16 Source | |
| FromJSValue Int32 Source | |
| FromJSValue Int64 Source | |
| FromJSValue Integer Source | |
| FromJSValue String Source | |
| FromJSValue ByteString Source | |
| FromJSValue JSValue Source | |
| FromJSValue a => FromJSValue [a] Source | |
| FromJSValue a => FromJSValue (Maybe a) Source | Parsing any Maybe always returns Just |
| (FromJSValue a, FromJSValue b) => FromJSValue (a, b) Source | |
| (FromJSValue a, FromJSValue b, FromJSValue c) => FromJSValue (a, b, c) Source | |
| (FromJSValue a, FromJSValue b, FromJSValue c, FromJSValue d) => FromJSValue (a, b, c, d) Source | |
| (FromJSValue a, FromJSValue b, FromJSValue c, FromJSValue d, FromJSValue e) => FromJSValue (a, b, c, d, e) Source | |
| (FromJSValue a, FromJSValue b, FromJSValue c, FromJSValue d, FromJSValue e, FromJSValue f) => FromJSValue (a, b, c, d, e, f) Source |
class FromJSValueWithUpdate a where Source
Structures that can be parsed from JSON, fields absent in the
JSON will be filled in using (optional) original structure.
By convention JSON null should be treated as a request to reset structure element to default value.
Minimal complete definition
Nothing
Methods
fromJSValueWithUpdate :: Maybe a -> JSValue -> Maybe a Source
fromJSValueWithUpdateM :: MonadReader JSValue m => Maybe a -> m (Maybe a) Source
class MatchWithJSValue a where Source
Structures that can be matched with JSValue
Minimal complete definition
Nothing
Methods
matchesWithJSValue :: a -> JSValue -> Bool Source
matchesWithJSValueM :: MonadReader JSValue m => a -> m Bool Source
Data Extraction
jsValueField :: (MonadReader JSValue m, FromJSValue a) => String -> m (Maybe (Maybe a)) Source
Reading the value that is on some field. Returns Nothing if
JSON is not an object or field is present but cannot be parsed,
'Just Nothing' if absent, and 'Just (Just a)' otherwise
fromJSValueField :: (MonadReader JSValue m, FromJSValue a) => String -> m (Maybe a) Source
Reading the value that is on a field. Semantics are a bit involved, example GHCi session should clarify:
Prelude> :set -XNoMonomorphismRestriction
Prelude> let x = withJSValue (JSObject (toJSObject [("key",JSString $ toJSString "value")]))
Prelude> x (fromJSValueField "key") :: IO (Maybe Int)
Nothing
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe Int))
Just Nothing
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe (Maybe Int)))
Just (Just Nothing)
Prelude> x (fromJSValueField "key") :: IO (Maybe String)
Just "value"
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe String))
Just (Just "value")
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe (Maybe String)))
Just (Just (Just "value"))
Prelude> let x = withJSValue (JSArray [])
Prelude> x (fromJSValueField "key") :: IO (Maybe String)
Nothing
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe String))
Nothing
Prelude> x (fromJSValueField "key") :: IO (Maybe (Maybe (Maybe String)))
NothingfromJSValueFieldBase64 :: MonadReader JSValue m => String -> m (Maybe ByteString) Source
Version of fromJSValueField for Base64 encoded data to avoid
memory leak.
fromJSValueFieldCustom :: MonadReader JSValue m => String -> m (Maybe a) -> m (Maybe a) Source
Generalization of fromJSValueField. Does not use FromJSValue
instances.
fromJSValueCustomMany :: MonadReader JSValue m => m (Maybe a) -> m (Maybe [a]) Source
Runs parser on each element of underlaying json. Returns Just iff JSON is array.
fromJSValueCustomList :: MonadReader JSValue m => [m (Maybe a)] -> m (Maybe [a]) Source
Generalization of fromJSValueCustomMany, where each element of
array can have different parser.
fromJSValueManyWithUpdate :: (MonadReader JSValue m, FromJSValueWithUpdate a, MatchWithJSValue a) => [a] -> m (Maybe [a]) Source
Runs parser on each element of underlying json. Returns Just iff
JSON is an array.
Note: This method has quadratic complexity. It is better to write less general matching algorithms that use Maps.
Running
withJSValue :: Monad m => JSValue -> ReaderT JSValue m a -> m a Source
Simple runner. Example:
let (v :: MyStruct) = runIdentity $ withJSValue js (fromJSValueM)
or inline:
let z = runIdentity $ withJSValue js $ do
a <- fromJSValueField "a"
b <- fromJSValueField "b"
c <- fromJSValueField "c"
return ((,,) <$> a <*> b <*> c)or using the monad transformer:
z <- withJSValue js $ do
a <- fromJSValueField "a"
b <- fromJSValueField "b"
c <- fromJSValueField "c"
return ((,,) <$> a <*> b <*> c)