tyro-0.3.0.0: Type derived JSON parsing using Aeson

Copyright(c) Richard Lupton 2017
LicenseBSD-3
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Data.Tyro

Contents

Description

 

Synopsis

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 parsed

type Extract a = JSBranch JSExtract a Source #

Extract a represents trying to parse JSON to an a.

type family (x :: Symbol) >%> (b :: *) :: * infixr 9 Source #

The type operator '>%> provides a way of describing how to walk down a JSON tree.

Instances

type x >%> (JSBranch xs a) Source # 
type x >%> (JSBranch xs a)

type family List (x :: *) :: * Source #

The List type operator constructs a parsing type for parsing a list of JSON objects.

Instances

type List (JSBranch xs a) Source # 
type List (JSBranch xs a)

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..

data Tyro Source #

Tyro is an abstract type representing a parser that walks down a JSON tree.

Instances

Eq Tyro Source # 

Methods

(==) :: Tyro -> Tyro -> Bool #

(/=) :: Tyro -> Tyro -> Bool #

Show Tyro Source # 

Methods

showsPrec :: Int -> Tyro -> ShowS #

show :: Tyro -> String #

showList :: [Tyro] -> ShowS #

extract :: Tyro Source #

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.

(%%>) :: FromJSON a => ByteString -> Tyro -> Maybe a infixl 8 Source #

%%> tries to parse a ByteString along a Tyro to obtain a value

Internal types

data JSBranch :: JSLens Symbol -> * -> * Source #

JSBranch is a dependent datatype which represents a walk down a JSON tree. JSBranch ["key1", "key2"] a represents the walk "take the value at key1 and then the value at key2, and (try to) interpret that as an a".

Instances

(FromJSON a, SingI (JSLens Symbol) xs) => FromJSON (JSBranch xs a) Source # 
type x >%> (JSBranch xs a) Source # 
type x >%> (JSBranch xs a)
type List (JSBranch xs a) Source # 
type List (JSBranch xs a)

type family Unwrap (x :: *) :: * Source #

Unwrap captures the unstructured type encapsulated by a JSBranch