hjsonpointer-1.5.0: JSON Pointer library

Safe HaskellNone
LanguageHaskell2010

JSONPointer

Contents

Synopsis

Resolution

Main types and escaping

newtype Pointer Source #

Constructors

Pointer 

Fields

Instances
Eq Pointer Source # 
Instance details

Defined in JSONPointer

Methods

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

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

Show Pointer Source # 
Instance details

Defined in JSONPointer

Generic Pointer Source # 
Instance details

Defined in JSONPointer

Associated Types

type Rep Pointer :: * -> * #

Methods

from :: Pointer -> Rep Pointer x #

to :: Rep Pointer x -> Pointer #

Semigroup Pointer Source # 
Instance details

Defined in JSONPointer

Monoid Pointer Source # 
Instance details

Defined in JSONPointer

Hashable Pointer Source # 
Instance details

Defined in JSONPointer

Methods

hashWithSalt :: Int -> Pointer -> Int #

hash :: Pointer -> Int #

ToJSON Pointer Source # 
Instance details

Defined in JSONPointer

FromJSON Pointer Source # 
Instance details

Defined in JSONPointer

type Rep Pointer Source # 
Instance details

Defined in JSONPointer

type Rep Pointer = D1 (MetaData "Pointer" "JSONPointer" "hjsonpointer-1.5.0-UNV7M5POQMBievPiLAgMk" True) (C1 (MetaCons "Pointer" PrefixI True) (S1 (MetaSel (Just "_unPointer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Token])))

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 # 
Instance details

Defined in JSONPointer

Methods

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

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

Show Token Source # 
Instance details

Defined in JSONPointer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in JSONPointer

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

Hashable Token Source # 
Instance details

Defined in JSONPointer

Methods

hashWithSalt :: Int -> Token -> Int #

hash :: Token -> Int #

type Rep Token Source # 
Instance details

Defined in JSONPointer

type Rep Token = D1 (MetaData "Token" "JSONPointer" "hjsonpointer-1.5.0-UNV7M5POQMBievPiLAgMk" True) (C1 (MetaCons "Token" PrefixI True) (S1 (MetaSel (Just "_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 
Instances
Eq FormatError Source # 
Instance details

Defined in JSONPointer

Show FormatError Source # 
Instance details

Defined in JSONPointer

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

These aren't used by the rest of the library (as explained in the docs for Token).

However, they might be useful if you need to distinguish JSON Pointer tokens from plain Text or Int without losing information by converting to Token.

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 # 
Instance details

Defined in JSONPointer

Methods

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

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

Show Key Source # 
Instance details

Defined in JSONPointer

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 
Instance details

Defined in JSONPointer

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Hashable Key Source # 
Instance details

Defined in JSONPointer

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

type Rep Key Source # 
Instance details

Defined in JSONPointer

type Rep Key = D1 (MetaData "Key" "JSONPointer" "hjsonpointer-1.5.0-UNV7M5POQMBievPiLAgMk" True) (C1 (MetaCons "Key" PrefixI True) (S1 (MetaSel (Just "_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 # 
Instance details

Defined in JSONPointer

Methods

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

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

Show Index Source # 
Instance details

Defined in JSONPointer

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Generic Index Source # 
Instance details

Defined in JSONPointer

Associated Types

type Rep Index :: * -> * #

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

Hashable Index Source # 
Instance details

Defined in JSONPointer

Methods

hashWithSalt :: Int -> Index -> Int #

hash :: Index -> Int #

type Rep Index Source # 
Instance details

Defined in JSONPointer

type Rep Index = D1 (MetaData "Index" "JSONPointer" "hjsonpointer-1.5.0-UNV7M5POQMBievPiLAgMk" True) (C1 (MetaCons "Index" PrefixI True) (S1 (MetaSel (Just "_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.