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

Typson.Esqueleto

Description

 
Synopsis

Documentation

jsonPath Source #

Arguments

:: (TypeAtPath o tree path ~ field, ReflectPath path, PostgreSqlJSON json) 
=> proxy (path :: k)

A path proxy

-> ObjectTree tree o

Typson schema

-> SqlExpr (Value (json o))

Column selector

-> SqlExpr (Value (NullableJSONB field)) 

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

select . from $ entity ->
  pure . jsonPath (Proxy @("foo" :-> "bar")) fieldSchemaJ
    $ entity ^. Field

newtype NullableJSONB a Source #

Treats SQL NULL as a JSON null

Constructors

NullableJSONB 

Fields

Instances

Instances details
Functor NullableJSONB Source # 
Instance details

Defined in Typson.Esqueleto

Methods

fmap :: (a -> b) -> NullableJSONB a -> NullableJSONB b #

(<$) :: a -> NullableJSONB b -> NullableJSONB a #

Foldable NullableJSONB Source # 
Instance details

Defined in Typson.Esqueleto

Methods

fold :: Monoid m => NullableJSONB m -> m #

foldMap :: Monoid m => (a -> m) -> NullableJSONB a -> m #

foldMap' :: Monoid m => (a -> m) -> NullableJSONB a -> m #

foldr :: (a -> b -> b) -> b -> NullableJSONB a -> b #

foldr' :: (a -> b -> b) -> b -> NullableJSONB a -> b #

foldl :: (b -> a -> b) -> b -> NullableJSONB a -> b #

foldl' :: (b -> a -> b) -> b -> NullableJSONB a -> b #

foldr1 :: (a -> a -> a) -> NullableJSONB a -> a #

foldl1 :: (a -> a -> a) -> NullableJSONB a -> a #

toList :: NullableJSONB a -> [a] #

null :: NullableJSONB a -> Bool #

length :: NullableJSONB a -> Int #

elem :: Eq a => a -> NullableJSONB a -> Bool #

maximum :: Ord a => NullableJSONB a -> a #

minimum :: Ord a => NullableJSONB a -> a #

sum :: Num a => NullableJSONB a -> a #

product :: Num a => NullableJSONB a -> a #

Traversable NullableJSONB Source # 
Instance details

Defined in Typson.Esqueleto

Methods

traverse :: Applicative f => (a -> f b) -> NullableJSONB a -> f (NullableJSONB b) #

sequenceA :: Applicative f => NullableJSONB (f a) -> f (NullableJSONB a) #

mapM :: Monad m => (a -> m b) -> NullableJSONB a -> m (NullableJSONB b) #

sequence :: Monad m => NullableJSONB (m a) -> m (NullableJSONB a) #

PostgreSqlJSON NullableJSONB Source # 
Instance details

Defined in Typson.Esqueleto

Eq a => Eq (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

Ord a => Ord (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

Read a => Read (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

Show a => Show (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

Generic (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

Associated Types

type Rep (NullableJSONB a) :: Type -> Type #

ToJSON a => ToJSON (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

FromJSON a => FromJSON (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

(FromJSON a, ToJSON a) => PersistField (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

(FromJSON a, ToJSON a) => PersistFieldSql (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

type Rep (NullableJSONB a) Source # 
Instance details

Defined in Typson.Esqueleto

type Rep (NullableJSONB a) = D1 ('MetaData "NullableJSONB" "Typson.Esqueleto" "typson-esqueleto-0.1.0.0-inplace" 'True) (C1 ('MetaCons "NullableJSONB" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNullableJSONB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

class PostgreSqlJSON (json :: * -> *) Source #

Members of this class are type constructors used to respresent Postgres JSON columns.

Instances

Instances details
PostgreSqlJSON JSONB Source # 
Instance details

Defined in Typson.Esqueleto

PostgreSqlJSON NullableJSONB Source # 
Instance details

Defined in Typson.Esqueleto