derulo-0.0.3: Parse and render JSON simply.

Safe HaskellSafe
LanguageHaskell2010

Derulo

Contents

Description

Derulo parses and renders JSON simply. It aims to provide an RFC 7159 compliant parser and renderer without incurring any dependencies. It is intended to be used either for learning or in situations where dependencies are unwanted. In normal usage, prefer a faster, more robust library like Aeson.

Derulo does not export any identifiers that conflict with the prelude and can be imported unqualified.

>>> import Derulo

Use readJSON to parse a String into a JSON value.

>>> readJSON " null "
Just Null

Use showJSON to render a JSON value as a String.

>>> showJSON Null
"null"

Synopsis

Types

data JSON Source #

A JSON value as described by RFC 7159.

Instances

Eq JSON Source # 

Methods

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

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

Data JSON Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JSON -> c JSON #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JSON #

toConstr :: JSON -> Constr #

dataTypeOf :: JSON -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c JSON) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JSON) #

gmapT :: (forall b. Data b => b -> b) -> JSON -> JSON #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JSON -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JSON -> r #

gmapQ :: (forall d. Data d => d -> u) -> JSON -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JSON -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JSON -> m JSON #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JSON -> m JSON #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JSON -> m JSON #

Ord JSON Source # 

Methods

compare :: JSON -> JSON -> Ordering #

(<) :: JSON -> JSON -> Bool #

(<=) :: JSON -> JSON -> Bool #

(>) :: JSON -> JSON -> Bool #

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

max :: JSON -> JSON -> JSON #

min :: JSON -> JSON -> JSON #

Read JSON Source # 
Show JSON Source # 

Methods

showsPrec :: Int -> JSON -> ShowS #

show :: JSON -> String #

showList :: [JSON] -> ShowS #

Generic JSON Source # 

Associated Types

type Rep JSON :: * -> * #

Methods

from :: JSON -> Rep JSON x #

to :: Rep JSON x -> JSON #

type Rep JSON Source # 

Parsing

readJSON :: String -> Maybe JSON Source #

Parses a string as JSON.

>>> readJSON "null"
Just Null
>>> readJSON "true"
Just (Boolean True)
>>> readJSON "false"
Just (Boolean False)
>>> readJSON "0e0"
Just (Number 0 0)
>>> readJSON "12e34"
Just (Number 12 34)
>>> readJSON "-12e-34"
Just (Number (-12) (-34))
>>> readJSON "\"\""
Just (String "")
>>> readJSON "\"js\""
Just (String "js")
>>> readJSON "\"\\\"\\\\\\b\\f\\n\\r\\t\""
Just (String "\"\\\b\f\n\r\t")
>>> readJSON "\"\\u001f\""
Just (String "\US")
>>> readJSON "[]"
Just (Array [])
>>> readJSON "[null]"
Just (Array [Null])
>>> readJSON "[true,false]"
Just (Array [Boolean True,Boolean False])
>>> readJSON "{}"
Just (Object [])
>>> readJSON "{\"\":null}"
Just (Object [("",Null)])
>>> readJSON "{\"t\":true,\"f\":false}"
Just (Object [("t",Boolean True),("f",Boolean False)])

Rendering

showJSON :: JSON -> String Source #

Renders JSON as a string.

>>> showJSON Null
"null"
>>> showJSON (Boolean True)
"true"
>>> showJSON (Boolean False)
"false"
>>> showJSON (Number 0 0)
"0e0"
>>> showJSON (Number 12 34)
"12e34"
>>> showJSON (Number (-12) (-34))
"-12e-34"
>>> showJSON (String "")
"\"\""
>>> showJSON (String "js")
"\"js\""
>>> showJSON (String "\"\\\b\f\n\r\t")
"\"\\\"\\\\\\b\\f\\n\\r\\t\""
>>> showJSON (String "\x1f")
"\"\\u001f\""
>>> showJSON (Array [])
"[]"
>>> showJSON (Array [Null])
"[null]"
>>> showJSON (Array [Boolean True, Boolean False])
"[true,false]"
>>> showJSON (Object [])
"{}"
>>> showJSON (Object [("", Null)])
"{\"\":null}"
>>> showJSON (Object [("t", Boolean True), ("f", Boolean False)])
"{\"t\":true,\"f\":false}"

Helpers

padLeft :: Integer -> a -> [a] -> [a] Source #

padRight :: Integer -> a -> [a] -> [a] Source #

sBetween :: ShowS -> ShowS -> (anything -> ShowS) -> anything -> ShowS Source #

sSeparated :: ShowS -> (element -> ShowS) -> [element] -> ShowS Source #

sSeparatedBetween :: ShowS -> ShowS -> ShowS -> (element -> ShowS) -> [element] -> ShowS Source #