| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Persist.Postgresql.JSON
Contents
Description
Filter operators for JSON values added to PostgreSQL 9.4
Synopsis
- (@>.) :: EntityField record Value -> Value -> Filter record
 - (<@.) :: EntityField record Value -> Value -> Filter record
 - (?.) :: EntityField record Value -> Text -> Filter record
 - (?|.) :: EntityField record Value -> [Text] -> Filter record
 - (?&.) :: EntityField record Value -> [Text] -> Filter record
 - data Value
 
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
(?.) :: EntityField record Value -> Text -> Filter record infix 4 Source #
This operator takes a column and a string to find a top-level key/field in an object.
column ?. string
N.B. This operator might have some unexpected interactions with non-object values. Please reference the examples.
Objects
{"a":null}             ? "a"  == True
{"test":false,"a":500} ? "a"  == True
{"b":{"a":[]}}         ? "a"  == False
{}                     ? "a"  == False
{}                     ? "{}" == False
{}                     ? ""   == False
{"":9001}              ? ""   == True
Arrays
This operator will match an array if the string to be matched is an element of that array, but nothing else.
["a"]              ? "a"   == True
[["a"]]            ? "a"   == False
[9,false,"1",null] ? "1"   == True
[]                 ? "[]"  == False
[{"a":true}]       ? "a"   == False
Other values
This operator functions like an equivalence operator on strings only. Any other value does not match.
"a" ? "a" == True "1" ? "1" == True "ab" ? "a" == False 1 ? "1" == False null ? "null" == False true ? "true" == False 1.5 ? "1.5" == False
Since: 2.10.0
(?|.) :: EntityField record Value -> [Text] -> Filter record infix 4 Source #
This operator takes a column and a list of strings to test whether ANY of the elements of the list are top level fields in an object.
column ?|. list
N.B. An empty list will never match anything. Also, this operator might have some unexpected interactions with non-object values. Please reference the examples.
Objects
{"a":null}                 ?| ["a","b","c"] == True
{"test":false,"a":500}     ?| ["a","b","c"] == True
{}                         ?| ["a","{}"]    == False
{"b":{"a":[]}}             ?| ["a","c"]     == False
{"b":{"a":[]},"test":null} ?| []            == False
Arrays
This operator will match an array if any of the elements of the list are matching string elements of the array.
["a"]              ?| ["a","b","c"] == True
[["a"]]            ?| ["a","b","c"] == False
[9,false,"1",null] ?| ["a","false"] == False
[]                 ?| ["a","b","c"] == False
[]                 ?| []            == False
[{"a":true}]       ?| ["a","b","c"] == False
[null,4,"b",[]]    ?| ["a","b","c"] == True
Other values
This operator functions much like an equivalence operator on strings only. If a string matches with any element of the given list, the comparison matches. No other values match.
"a" ?| ["a","b","c"] == True "1" ?| ["a","b","1"] == True "ab" ?| ["a","b","c"] == False 1 ?| ["a","1"] == False null ?| ["a","null"] == False true ?| ["a","true"] == False "a" ?| [] == False
Since: 2.10.0
(?&.) :: EntityField record Value -> [Text] -> Filter record infix 4 Source #
This operator takes a column and a list of strings to test whether ALL of the elements of the list are top level fields in an object.
column ?&. list
N.B. An empty list will match anything. Also, this operator might have some unexpected interactions with non-object values. Please reference the examples.
Objects
{"a":null}                 ?& ["a"]         == True
{"a":null}                 ?& ["a","a"]     == True
{"test":false,"a":500}     ?& ["a"]         == True
{"test":false,"a":500}     ?& ["a","b"]     == False
{}                         ?& ["{}"]        == False
{"b":{"a":[]}}             ?& ["a"]         == False
{"b":{"a":[]},"c":false}   ?& ["a","c"]     == False
{"a":1,"b":2,"c":3,"d":4}  ?& ["b","d"]     == True
{}                         ?& []            == True
{"b":{"a":[]},"test":null} ?& []            == True
Arrays
This operator will match an array if all of the elements of the list are matching string elements of the array.
["a"]                   ?& ["a"]         == True
["a"]                   ?& ["a","a"]     == True
[["a"]]                 ?& ["a"]         == False
["a","b","c"]           ?& ["a","b","d"] == False
[9,"false","1",null]    ?& ["1","false"] == True
[]                      ?& ["a","b"]     == False
[{"a":true}]            ?& ["a"]         == False
["a","b","c","d"]       ?& ["b","c","d"] == True
[null,4,{"test":false}] ?& []            == True
[]                      ?& []            == True
Other values
This operator functions much like an equivalence operator on strings only. If a string matches with all elements of the given list, the comparison matches.
"a" ?& ["a"] == True "1" ?& ["a","1"] == False "b" ?& ["b","b"] == True "ab" ?& ["a","b"] == False 1 ?& ["1"] == False null ?& ["null"] == False true ?& ["true"] == False 31337 ?& [] == True true ?& [] == True null ?& [] == True
Since: 2.10.0
A JSON value represented as a Haskell value.
Instances
| Eq Value | |
| Data Value | |
Defined in Data.Aeson.Types.Internal 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 # 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 :: forall r r'. (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 #  | |
| Ord Value | The ordering is total, consistent with  Since: aeson-1.5.2.0  | 
| Read Value | |
| Show Value | Since version 1.5.6.0 version object values are printed in lexicographic key order 
 
  | 
| IsString Value | |
Defined in Data.Aeson.Types.Internal Methods fromString :: String -> Value #  | |
| Generic Value | |
| Function Value | Since: aeson-2.0.3.0  | 
| Arbitrary Value | Since: aeson-2.0.3.0  | 
| CoArbitrary Value | Since: aeson-2.0.3.0  | 
Defined in Data.Aeson.Types.Internal Methods coarbitrary :: Value -> Gen b -> Gen b #  | |
| Hashable Value | |
Defined in Data.Aeson.Types.Internal  | |
| ToJSON Value | |
Defined in Data.Aeson.Types.ToJSON  | |
| KeyValue Object | Constructs a singleton   | 
| KeyValue Pair | |
| FromJSON Value | |
| NFData Value | |
Defined in Data.Aeson.Types.Internal  | |
| PersistFieldSql Value Source # | |
| PersistField Value Source # | |
Defined in Database.Persist.Postgresql.JSON Methods toPersistValue :: Value -> PersistValue # fromPersistValue :: PersistValue -> Either Text Value #  | |
| FromField Value | json, jsonb  | 
Defined in Database.PostgreSQL.Simple.FromField Methods  | |
| ToField Value | |
Defined in Database.PostgreSQL.Simple.ToField  | |
| FromString Encoding | |
Defined in Data.Aeson.Types.ToJSON Methods fromString :: String -> Encoding  | |
| FromString Value | |
Defined in Data.Aeson.Types.ToJSON Methods fromString :: String -> Value  | |
| Lift Value | Since: aeson-0.11.0.0  | 
| GToJSON' Encoding arity (U1 :: Type -> Type) | |
| GToJSON' Value arity (V1 :: Type -> Type) | |
| GToJSON' Value arity (U1 :: Type -> Type) | |
| ToJSON1 f => GToJSON' Encoding One (Rec1 f) | |
| ToJSON1 f => GToJSON' Value One (Rec1 f) | |
| ToJSON a => GToJSON' Encoding arity (K1 i a :: Type -> Type) | |
| (EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) | |
| ToJSON a => GToJSON' Value arity (K1 i a :: Type -> Type) | |
| (WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |
| (ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) | |
| (ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) | |
| FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON  | |
| v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON  | |
| (GToJSON' Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON  | |
| (GToJSON' Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) | |
Defined in Data.Aeson.Types.ToJSON  | |
| type Rep Value | |
Defined in Data.Aeson.Types.Internal type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Types.Internal" "aeson-2.0.3.0-97vyUsLYXCMAtxiWk6tvis" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Array)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Scientific)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type))))  | |
Orphan instances
| PersistFieldSql Value Source # | |
| PersistField Value Source # | |
Methods toPersistValue :: Value -> PersistValue # fromPersistValue :: PersistValue -> Either Text Value #  | |