| Copyright | (c) Richard Lupton 2017 |
|---|---|
| License | BSD-3 |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Tyro
Description
- type Extract a = JSBranch JSExtract a
- type family (x :: Symbol) >%> (b :: *) :: *
- type family List (x :: *) :: *
- unwrap :: JSBranch xs a -> Unwrap (JSBranch xs a)
- data Tyro
- extract :: Tyro
- (>%>) :: String -> Tyro -> Tyro
- (%%>) :: FromJSON a => ByteString -> Tyro -> Maybe a
- data JSBranch :: JSLens Symbol -> * -> *
- type family Unwrap (x :: *) :: *
Introduction
Tyro provides a type driven way of obtaining simple JSON parsers, and
a simple value driven interface to obtain values deep inside a JSON object.
Building types
A small (artificial) example demonstrating how to use the typed interface.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
import Data.Tyro
import Data.Aeson (decode)
import qualified Data.ByteString.Lazy as B
json = "{\"key1\":[{\"key2\":41},{\"key2\":42}]}" :: B.ByteString
-- Extract [41, 42] inside the Tyro types
parsed = decode json :: Maybe ("key1" >%> List ("key2" >%> Extract Integer))
-- We can dispose of the types using unwrap: 'values' will have the value
-- Just [41, 42]
values :: Maybe [Integer]
values = fmap unwrap parsedtype family (x :: Symbol) >%> (b :: *) :: * infixr 9 Source #
The type operator '>%> provides a way of describing how to walk down a JSON tree.
type family List (x :: *) :: * Source #
The List type operator constructs a parsing type for parsing
a list of JSON objects.
unwrap :: JSBranch xs a -> Unwrap (JSBranch xs a) Source #
unwrap allows parsing types to be removed from a JSBranch
Value level API
(Experimental!) The value level interface allows a piece of the JSON object to be extracted in a similar way to most dynamically typed languages.
{-# LANGUAGE OverloadedStrings #-}
import Data.Tyro
json = "{\"key1\": {\"key2\" : [41, 42]}}" :: B.ByteString
-- Extract [41, 42] inside the JSON
parsed = json %%> "key1" >%> "key2" >%> extract :: Maybe [Integer]Not the overloaded strings extension in the above is only used to define
the json ByteString..
Tyro is an abstract type representing a parser that walks down a JSON
tree.
extract is the value which represents halting the walk along the JSON
tree, and pulling out the value there.
(>%>) :: String -> Tyro -> Tyro infixr 9 Source #
>%> allows you to specify a subtree indexed by a key. It's right
associative, so chains of keys can be specified without parenthesese.