persistent-postgresql-2.8.2.0: Backend for the persistent library using postgresql.

Safe HaskellNone
LanguageHaskell98

Database.Persist.Postgresql.JSON

Contents

Description

Filter operators for JSON values added to PostgreSQL 9.4

Synopsis

Documentation

(@>.) :: EntityField record Value -> Value -> Filter record infix 4 Source #

This operator checks inclusion of the JSON value on the right hand side in the JSON value on the left hand side.

Objects

An empty Object matches any object

{}                @> {} == True
{"a":1,"b":false} @> {} == True

Any key-value will be matched top-level

{"a":1,"b":{"c":true"}} @> {"a":1}         == True
{"a":1,"b":{"c":true"}} @> {"b":1}         == False
{"a":1,"b":{"c":true"}} @> {"b":{}}        == True
{"a":1,"b":{"c":true"}} @> {"c":true}      == False
{"a":1,"b":{"c":true"}} @> {"b":{c":true}} == True

Arrays

An empty Array matches any array

[]                    @> [] == True
[1,2,"hi",false,null] @> [] == True

Any array has to be a sub-set. Any object or array will also be compared as being a subset of.

[1,2,"hi",false,null] @> [1]                       == True
[1,2,"hi",false,null] @> [null,"hi"]               == True
[1,2,"hi",false,null] @> ["hi",true]               == False
[1,2,"hi",false,null] @> ["hi",2,null,false,1]     == True
[1,2,"hi",false,null] @> [1,2,"hi",false,null,{}]  == False

Arrays and objects inside arrays match the same way they'd be matched as being on their own.

[1,"hi",[false,3],{"a":[null]}] @> [{}]            == True
[1,"hi",[false,3],{"a":[null]}] @> [{"a":[]}]      == True
[1,"hi",[false,3],{"a":[null]}] @> [{"b":[null]}]  == False
[1,"hi",[false,3],{"a":[null]}] @> [[]]            == True
[1,"hi",[false,3],{"a":[null]}] @> [[3]]           == True
[1,"hi",[false,3],{"a":[null]}] @> [[true,3]]      == False

A regular value has to be a member

[1,2,"hi",false,null] @> 1      == True
[1,2,"hi",false,null] @> 5      == False
[1,2,"hi",false,null] @> "hi"   == True
[1,2,"hi",false,null] @> false  == True
[1,2,"hi",false,null] @> "2"    == False

An object will never match with an array

[1,2,"hi",[false,3],{"a":null}] @> {}          == False
[1,2,"hi",[false,3],{"a":null}] @> {"a":null}  == False

Other values

For any other JSON values the `(@>.)` operator functions like an equivalence operator.

"hello" @> "hello"     == True
"hello" @> "Hello"     == False
"hello" @> "h"         == False
"hello" @> {"hello":1} == False
"hello" @> ["hello"]   == False

5       @> 5       == True
5       @> 5.00    == True
5       @> 1       == False
5       @> 7       == False
12345   @> 1234    == False
12345   @> 2345    == False
12345   @> "12345" == False
12345   @> [1,2,3,4,5] == False

true    @> true    == True
true    @> false   == False
false   @> true    == False
true    @> "true"  == False

null    @> null    == True
null    @> 23      == False
null    @> "null"  == False
null    @> {}      == False

Since: 2.8.2

(<@.) :: EntityField record Value -> Value -> Filter record infix 4 Source #

Same as @>. except the inclusion check is reversed. i.e. is the JSON value on the left hand side included in the JSON value of the right hand side.

Since: 2.8.2

data Value :: * #

A JSON value represented as a Haskell value.

Instances

Eq Value 

Methods

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

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

Data Value 

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Value 
Show Value 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value 

Methods

fromString :: String -> Value #

Generic Value 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Lift Value 

Methods

lift :: Value -> Q Exp #

FromString Encoding 
FromString Value 

Methods

fromString :: String -> Value

Hashable Value 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

ToJSON Value 
KeyValue Pair 

Methods

(.=) :: ToJSON v => Text -> v -> Pair #

FromJSON Value 
NFData Value 

Methods

rnf :: Value -> () #

FromField Value

json

ToField Value 

Methods

toField :: Value -> Action #

FromPairs Encoding Series 
GKeyValue Encoding Series 

Methods

gPair :: String -> Encoding -> Series

GToJSON Encoding arity (U1 *) 

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> U1 * a -> Encoding

GToJSON Value arity (U1 *) 

Methods

gToJSON :: Options -> ToArgs Value arity a -> U1 * a -> Value

ToJSON1 f => GToJSON Encoding One (Rec1 * f) 

Methods

gToJSON :: Options -> ToArgs Encoding One a -> Rec1 * f a -> Encoding

ToJSON1 f => GToJSON Value One (Rec1 * f) 

Methods

gToJSON :: Options -> ToArgs Value One a -> Rec1 * f a -> Value

ToJSON a => GToJSON Encoding arity (K1 * i a) 

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> K1 * i a a -> Encoding

(EncodeProduct arity a, EncodeProduct arity b) => GToJSON Encoding arity ((:*:) * a b) 

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> (* :*: a) b a -> Encoding

ToJSON a => GToJSON Value arity (K1 * i a) 

Methods

gToJSON :: Options -> ToArgs Value arity a -> K1 * i a a -> Value

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON Value arity ((:*:) * a b) 

Methods

gToJSON :: Options -> ToArgs Value arity a -> (* :*: a) b a -> Value

(ToJSON1 f, GToJSON Encoding One g) => GToJSON Encoding One ((:.:) * * f g) 

Methods

gToJSON :: Options -> ToArgs Encoding One a -> (* :.: *) f g a -> Encoding

(ToJSON1 f, GToJSON Value One g) => GToJSON Value One ((:.:) * * f g) 

Methods

gToJSON :: Options -> ToArgs Value One a -> (* :.: *) f g a -> Value

FromPairs Value (DList Pair) 

Methods

fromPairs :: DList Pair -> Value

ToJSON v => GKeyValue v (DList Pair) 

Methods

gPair :: String -> v -> DList Pair

(GToJSON Encoding arity a, ConsToJSON Encoding arity a, Constructor Meta c) => SumToJSON' * TwoElemArray Encoding arity (C1 * c a) 

Methods

sumToJSON' :: Options -> ToArgs arity (C1 * c a) a -> f a -> Tagged TwoElemArray Encoding arity

(GToJSON Value arity a, ConsToJSON Value arity a, Constructor Meta c) => SumToJSON' * TwoElemArray Value arity (C1 * c a) 

Methods

sumToJSON' :: Options -> ToArgs arity (C1 * c a) a -> f a -> Tagged TwoElemArray Value arity

type Rep Value 

Orphan instances