typson-beam-0.1.0.0
Copyright(c) Aaron Allen 2020
LicenseBSD-style (see the file LICENSE)
MaintainerAaron Allen <aaronallen8455@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Typson.Beam

Description

 
Synopsis

Documentation

jsonPath Source #

Arguments

:: (TypeAtPath o tree path ~ field, ReflectPath path, IsPgJSON json, Coercible (json field) (JNullable json' field)) 
=> proxy (path :: k)

A path proxy

-> ObjectTree tree o

Typson schema

-> QGenExpr ctxt Postgres s (json o)

Column selector

-> QGenExpr ctxt Postgres s (JNullable json' field) 

Use a type-safe JSON path as part of a query.

select $ jsonPath (Proxy @("foo" :-> "bar")) fieldSchemaJ
       . fieldAccessor
     <$> all_ someTable

newtype JNullable json a Source #

Wraps a PgJSON or PgJSONB, treating deserialization of SQL NULL as json null. This is so that if you query for a path that might not exist, i.e. a path into an optional field, then an exception will not be raised when attempting to decode the result as JSON.

Constructors

JNullable (json a) 

Instances

Instances details
HasSqlValueSyntax syn (json a) => HasSqlValueSyntax syn (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

Methods

sqlValueSyntax :: JNullable json a -> syn #

(FromField (json a), Typeable a, Typeable json) => FromBackendRow Postgres (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

IsPgJSON json => IsPgJSON (JNullable json) Source # 
Instance details

Defined in Typson.Beam

Eq (json a) => Eq (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

Methods

(==) :: JNullable json a -> JNullable json a -> Bool #

(/=) :: JNullable json a -> JNullable json a -> Bool #

Ord (json a) => Ord (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

Methods

compare :: JNullable json a -> JNullable json a -> Ordering #

(<) :: JNullable json a -> JNullable json a -> Bool #

(<=) :: JNullable json a -> JNullable json a -> Bool #

(>) :: JNullable json a -> JNullable json a -> Bool #

(>=) :: JNullable json a -> JNullable json a -> Bool #

max :: JNullable json a -> JNullable json a -> JNullable json a #

min :: JNullable json a -> JNullable json a -> JNullable json a #

Show (json a) => Show (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

Methods

showsPrec :: Int -> JNullable json a -> ShowS #

show :: JNullable json a -> String #

showList :: [JNullable json a] -> ShowS #

FromField (json a) => FromField (JNullable json a) Source # 
Instance details

Defined in Typson.Beam

Methods

fromField :: FieldParser (JNullable json a) #

nullableJsonb :: forall a. (ToJSON a, FromJSON a) => DataType Postgres (JNullable PgJSONB a) Source #

Declares a nullable PgJSONB field in a migration schema

nullableJson :: forall a. (ToJSON a, FromJSON a) => DataType Postgres (JNullable PgJSON a) Source #

Declares a nullable PgJSON field in a migration schema