hjsonpointer-1.2.0: JSON Pointer library

Safe HaskellNone
LanguageHaskell2010

JSONPointer

Contents

Synopsis

Resolution

Main types and escaping

newtype Pointer Source #

Constructors

Pointer 

Fields

newtype Token Source #

We don't try to distinguish between integer tokens and string tokens since all tokens start as strings, and all tokens can be used to resolve JSON objects.

Since these are unescaped you can write "/" and "~" normally. (e.g. if you're referencing a key such as "abc/123", go ahead and write that exactly.

Constructors

Token 

Fields

Instances

Eq Token Source # 

Methods

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

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

Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

Arbitrary Token Source # 

Methods

arbitrary :: Gen Token #

shrink :: Token -> [Token] #

Hashable Token Source # 

Methods

hashWithSalt :: Int -> Token -> Int #

hash :: Token -> Int #

type Rep Token Source # 
type Rep Token = D1 (MetaData "Token" "JSONPointer" "hjsonpointer-1.2.0-Dq9TT6F5ifvCvlvnSeQjOj" True) (C1 (MetaCons "Token" PrefixI True) (S1 (MetaSel (Just Symbol "_unToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

escape :: Pointer -> Text Source #

This escapes "/" (because it's the token separator character).

It also escapes "~" (because it's the escape character).

data FormatError Source #

Constructors

InvalidFirstChar

JSON Pointers must either be empty or start with a /.

UnescapedTilde 

unescape :: Text -> Either FormatError Pointer Source #

JSON Pointers must either be empty or start with a /. This means that if you're turning a URI Fragment into a JSON Pointer you must drop the initial #.

Note that the unescaping happening here is not the same as URI decoding. If you are turning a URI fragment into a JSON Pointer you must URI decode the Text before using it as an argument to this function. There's an example of how to do this in the tests using "Network.HTTP.Types.URI.urlDecode" from http-types.

Wrapper Types

newtype Key Source #

A glorified type alias. If you need to do JSON Pointer operations you're looking for Token instead.

NOTE: Unlike Token this is escaped.

Constructors

Key 

Fields

Instances

Eq Key Source # 

Methods

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

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

Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Hashable Key Source # 

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

type Rep Key Source # 
type Rep Key = D1 (MetaData "Key" "JSONPointer" "hjsonpointer-1.2.0-Dq9TT6F5ifvCvlvnSeQjOj" True) (C1 (MetaCons "Key" PrefixI True) (S1 (MetaSel (Just Symbol "_unKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Index Source #

A glorified type alias. If you need to do JSON Pointer operations you're looking for Token instead.

Constructors

Index 

Fields

Instances

Eq Index Source # 

Methods

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

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

Show Index Source # 

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Generic Index Source # 

Associated Types

type Rep Index :: * -> * #

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

Hashable Index Source # 

Methods

hashWithSalt :: Int -> Index -> Int #

hash :: Index -> Int #

type Rep Index Source # 
type Rep Index = D1 (MetaData "Index" "JSONPointer" "hjsonpointer-1.2.0-Dq9TT6F5ifvCvlvnSeQjOj" True) (C1 (MetaCons "Index" PrefixI True) (S1 (MetaSel (Just Symbol "_unIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

Internals

unescapeToken :: Text -> Maybe Token Source #

For internal use (by unescape).

resolveToken :: Token -> Value -> Either ResolutionError Value Source #

For internal use (by resolve).

Might also be useful for specialized applications that don't want to resolve an entire pointer at once.