| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Json.Parser
Contents
- parseJsonBs :: JsonReadable t => ByteString -> Either String t
- parseJsonBsl :: JsonReadable t => ByteString -> Either String t
- parseJsonT :: JsonReadable t => Text -> Either String t
- class JsonReadable t where
- runParseSpec :: ParseSpec k -> Parser k
- data ObjSpec ts where
- ObjSpecNil :: ObjSpec []
- (:&&:) :: (JsonReadable t, Typeable t) => !(TypedKey t) -> !(ObjSpec ts) -> ObjSpec (t : ts)
- data ParseSpec k where
- (:$:) :: HVectElim ts k -> ObjSpec ts -> ParseSpec k
- FirstConstr :: KeyedConstr k -> ParseSpec k
- (:|:) :: KeyedConstr k -> ParseSpec k -> ParseSpec k
- data KeyedConstr k
- (<||>) :: KeyedConstr k -> ParseSpec k -> ParseSpec k
- class ConstrTagger r where
- type ResultType r :: *
- (.->) :: Text -> Parser (ResultType r) -> r
- data TypedKey t
- reqKey :: Typeable t => Text -> TypedKey t
- optKey :: Typeable t => Text -> TypedKey (Maybe t)
- typedKeyKey :: TypedKey t -> Text
- readObject :: (Text -> Maybe (Parser a)) -> Parser (HashMap Text a)
- type Parser = Parser ByteString
- data WrappedValue = forall t . (Typeable t, JsonReadable t) => WrappedValue !t
- getValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m t
- getOptValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m (Maybe t)
Parsing from different types
parseJsonBs :: JsonReadable t => ByteString -> Either String t Source
Parse json from a strict ByteString
parseJsonBsl :: JsonReadable t => ByteString -> Either String t Source
Parse json from a lazy ByteString
parseJsonT :: JsonReadable t => Text -> Either String t Source
Parse json from a strict Text
Description how to parse JSON to a Haskell type
class JsonReadable t where Source
Typeclass defining an attoparsec Parser how Haskell types should
be parsed from JSON. Use predifined instances (with readJson) and
runSpec (on ObjSpec) to define instances for custom types
Instances
| JsonReadable Bool | |
| JsonReadable Double | |
| JsonReadable Int | |
| JsonReadable Int8 | |
| JsonReadable Int16 | |
| JsonReadable Int32 | |
| JsonReadable Int64 | |
| JsonReadable Word | |
| JsonReadable Word8 | |
| JsonReadable Word16 | |
| JsonReadable Word32 | |
| JsonReadable Word64 | |
| JsonReadable Text | |
| JsonReadable Scientific | |
| JsonReadable t => JsonReadable [t] | |
| JsonReadable t => JsonReadable (Maybe t) | |
| JsonReadable t => JsonReadable (Vector t) | |
| JsonReadable a => JsonReadable (HVect ((:) * a ([] *))) | |
| (JsonReadable a, JsonReadable b) => JsonReadable (Either a b) | |
| JsonReadable t => JsonReadable (t, t) |
DSL to easily create parser for custom Haskell types
List of TypedKeys, should be in the same order as your
constructor in runSpec will expect them
Constructors
| ObjSpecNil :: ObjSpec [] | |
| (:&&:) :: (JsonReadable t, Typeable t) => !(TypedKey t) -> !(ObjSpec ts) -> ObjSpec (t : ts) infixr 5 |
Parser specification. Use :$: for normal types and FirstConstr / :|: for sum types
Constructors
| (:$:) :: HVectElim ts k -> ObjSpec ts -> ParseSpec k infixr 4 | |
| FirstConstr :: KeyedConstr k -> ParseSpec k | |
| (:|:) :: KeyedConstr k -> ParseSpec k -> ParseSpec k |
Instances
| ConstrTagger (ParseSpec k) | |
| type ResultType (ParseSpec k) = k |
data KeyedConstr k Source
Associates a json key with a parser
Instances
| ConstrTagger (KeyedConstr k) | |
| type ResultType (KeyedConstr k) = k |
(<||>) :: KeyedConstr k -> ParseSpec k -> ParseSpec k infixr 3 Source
Choice between multiple constructors
class ConstrTagger r where Source
Associated Types
type ResultType r :: * Source
Instances
| ConstrTagger (ParseSpec k) | |
| ConstrTagger (KeyedConstr k) |
Json object key to a value t
reqKey :: Typeable t => Text -> TypedKey t Source
Required json object key. Use IsString instance for automatic choice
optKey :: Typeable t => Text -> TypedKey (Maybe t) Source
Optional json object key. Use IsString instance for automatic choice
typedKeyKey :: TypedKey t -> Text Source
Get the textual key of a TypedKey
Low level JSON parsing helpers
readObject :: (Text -> Maybe (Parser a)) -> Parser (HashMap Text a) Source
Parse a json object given a value parser for each key
type Parser = Parser ByteString
data WrappedValue Source
A value that is Typeable and JsonReadable
Constructors
| forall t . (Typeable t, JsonReadable t) => WrappedValue !t |
getValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m t Source
Get a value out of the map returned by readObject
getOptValueByKey :: (Monad m, Typeable t) => Text -> HashMap Text WrappedValue -> m (Maybe t) Source
Optionally get a value out of the map returned by readObject