graphql-engine-1.0.0: GraphQL API over Postgres
Safe HaskellNone
LanguageHaskell2010

Hasura.Backends.Postgres.Types.Update

Description

Postgres Types Update

This module defines the Update-related IR types specific to Postgres.

Synopsis

Documentation

data MultiRowUpdate pgKind v Source #

Represents an entry in an update_table_many update.

Constructors

MultiRowUpdate 

Fields

Instances

Instances details
Backend ('Postgres pgKind) => Functor (MultiRowUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

fmap :: (a -> b) -> MultiRowUpdate pgKind a -> MultiRowUpdate pgKind b #

(<$) :: a -> MultiRowUpdate pgKind b -> MultiRowUpdate pgKind a #

Backend ('Postgres pgKind) => Foldable (MultiRowUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

fold :: Monoid m => MultiRowUpdate pgKind m -> m #

foldMap :: Monoid m => (a -> m) -> MultiRowUpdate pgKind a -> m #

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

foldr :: (a -> b -> b) -> b -> MultiRowUpdate pgKind a -> b #

foldr' :: (a -> b -> b) -> b -> MultiRowUpdate pgKind a -> b #

foldl :: (b -> a -> b) -> b -> MultiRowUpdate pgKind a -> b #

foldl' :: (b -> a -> b) -> b -> MultiRowUpdate pgKind a -> b #

foldr1 :: (a -> a -> a) -> MultiRowUpdate pgKind a -> a #

foldl1 :: (a -> a -> a) -> MultiRowUpdate pgKind a -> a #

toList :: MultiRowUpdate pgKind a -> [a] #

null :: MultiRowUpdate pgKind a -> Bool #

length :: MultiRowUpdate pgKind a -> Int #

elem :: Eq a => a -> MultiRowUpdate pgKind a -> Bool #

maximum :: Ord a => MultiRowUpdate pgKind a -> a #

minimum :: Ord a => MultiRowUpdate pgKind a -> a #

sum :: Num a => MultiRowUpdate pgKind a -> a #

product :: Num a => MultiRowUpdate pgKind a -> a #

Backend ('Postgres pgKind) => Traversable (MultiRowUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

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

sequenceA :: Applicative f => MultiRowUpdate pgKind (f a) -> f (MultiRowUpdate pgKind a) #

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

sequence :: Monad m => MultiRowUpdate pgKind (m a) -> m (MultiRowUpdate pgKind a) #

(Eq (AnnBoolExpFld ('Postgres pgKind) v), Eq (UpdateOpExpression v), Backend ('Postgres pgKind)) => Eq (MultiRowUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

(==) :: MultiRowUpdate pgKind v -> MultiRowUpdate pgKind v -> Bool #

(/=) :: MultiRowUpdate pgKind v -> MultiRowUpdate pgKind v -> Bool #

(Data v, Typeable pgKind, Data (AnnBoolExpFld ('Postgres pgKind) v), Backend ('Postgres pgKind)) => Data (MultiRowUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MultiRowUpdate pgKind v -> c (MultiRowUpdate pgKind v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MultiRowUpdate pgKind v) #

toConstr :: MultiRowUpdate pgKind v -> Constr #

dataTypeOf :: MultiRowUpdate pgKind v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MultiRowUpdate pgKind v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MultiRowUpdate pgKind v)) #

gmapT :: (forall b. Data b => b -> b) -> MultiRowUpdate pgKind v -> MultiRowUpdate pgKind v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MultiRowUpdate pgKind v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MultiRowUpdate pgKind v -> r #

gmapQ :: (forall d. Data d => d -> u) -> MultiRowUpdate pgKind v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MultiRowUpdate pgKind v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MultiRowUpdate pgKind v -> m (MultiRowUpdate pgKind v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiRowUpdate pgKind v -> m (MultiRowUpdate pgKind v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiRowUpdate pgKind v -> m (MultiRowUpdate pgKind v) #

(Show (AnnBoolExpFld ('Postgres pgKind) v), Show (UpdateOpExpression v), Backend ('Postgres pgKind)) => Show (MultiRowUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

showsPrec :: Int -> MultiRowUpdate pgKind v -> ShowS #

show :: MultiRowUpdate pgKind v -> String #

showList :: [MultiRowUpdate pgKind v] -> ShowS #

Generic (MultiRowUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Associated Types

type Rep (MultiRowUpdate pgKind v) :: Type -> Type #

Methods

from :: MultiRowUpdate pgKind v -> Rep (MultiRowUpdate pgKind v) x #

to :: Rep (MultiRowUpdate pgKind v) x -> MultiRowUpdate pgKind v #

type Rep (MultiRowUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

type Rep (MultiRowUpdate pgKind v) = D1 ('MetaData "MultiRowUpdate" "Hasura.Backends.Postgres.Types.Update" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "MultiRowUpdate" 'PrefixI 'True) (S1 ('MetaSel ('Just "mruWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AnnBoolExp ('Postgres pgKind) v)) :*: S1 ('MetaSel ('Just "mruExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap PGCol (UpdateOpExpression v)))))

data BackendUpdate pgKind v Source #

The PostgreSQL-specific data of an Update expression.

This is parameterised over v which enables different phases of IR transformation to maintain the overall structure while enriching/transforming the data at the leaves.

Constructors

BackendUpdate (HashMap PGCol (UpdateOpExpression v))

The update operations to perform on each colum.

BackendMultiRowUpdate [MultiRowUpdate pgKind v]

The update operations to perform, in sequence, for an update_table_many operation.

Instances

Instances details
Backend ('Postgres pgKind) => Functor (BackendUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

fmap :: (a -> b) -> BackendUpdate pgKind a -> BackendUpdate pgKind b #

(<$) :: a -> BackendUpdate pgKind b -> BackendUpdate pgKind a #

Backend ('Postgres pgKind) => Foldable (BackendUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

fold :: Monoid m => BackendUpdate pgKind m -> m #

foldMap :: Monoid m => (a -> m) -> BackendUpdate pgKind a -> m #

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

foldr :: (a -> b -> b) -> b -> BackendUpdate pgKind a -> b #

foldr' :: (a -> b -> b) -> b -> BackendUpdate pgKind a -> b #

foldl :: (b -> a -> b) -> b -> BackendUpdate pgKind a -> b #

foldl' :: (b -> a -> b) -> b -> BackendUpdate pgKind a -> b #

foldr1 :: (a -> a -> a) -> BackendUpdate pgKind a -> a #

foldl1 :: (a -> a -> a) -> BackendUpdate pgKind a -> a #

toList :: BackendUpdate pgKind a -> [a] #

null :: BackendUpdate pgKind a -> Bool #

length :: BackendUpdate pgKind a -> Int #

elem :: Eq a => a -> BackendUpdate pgKind a -> Bool #

maximum :: Ord a => BackendUpdate pgKind a -> a #

minimum :: Ord a => BackendUpdate pgKind a -> a #

sum :: Num a => BackendUpdate pgKind a -> a #

product :: Num a => BackendUpdate pgKind a -> a #

Backend ('Postgres pgKind) => Traversable (BackendUpdate pgKind) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

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

sequenceA :: Applicative f => BackendUpdate pgKind (f a) -> f (BackendUpdate pgKind a) #

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

sequence :: Monad m => BackendUpdate pgKind (m a) -> m (BackendUpdate pgKind a) #

(Backend ('Postgres pgKind), Eq (MultiRowUpdate pgKind v), Eq (UpdateOpExpression v)) => Eq (BackendUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

(==) :: BackendUpdate pgKind v -> BackendUpdate pgKind v -> Bool #

(/=) :: BackendUpdate pgKind v -> BackendUpdate pgKind v -> Bool #

(Data v, Typeable pgKind, Data (AnnBoolExpFld ('Postgres pgKind) v), Backend ('Postgres pgKind)) => Data (BackendUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BackendUpdate pgKind v -> c (BackendUpdate pgKind v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BackendUpdate pgKind v) #

toConstr :: BackendUpdate pgKind v -> Constr #

dataTypeOf :: BackendUpdate pgKind v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BackendUpdate pgKind v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BackendUpdate pgKind v)) #

gmapT :: (forall b. Data b => b -> b) -> BackendUpdate pgKind v -> BackendUpdate pgKind v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BackendUpdate pgKind v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BackendUpdate pgKind v -> r #

gmapQ :: (forall d. Data d => d -> u) -> BackendUpdate pgKind v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BackendUpdate pgKind v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BackendUpdate pgKind v -> m (BackendUpdate pgKind v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BackendUpdate pgKind v -> m (BackendUpdate pgKind v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BackendUpdate pgKind v -> m (BackendUpdate pgKind v) #

(Backend ('Postgres pgKind), Show (MultiRowUpdate pgKind v), Show (UpdateOpExpression v)) => Show (BackendUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

showsPrec :: Int -> BackendUpdate pgKind v -> ShowS #

show :: BackendUpdate pgKind v -> String #

showList :: [BackendUpdate pgKind v] -> ShowS #

Generic (BackendUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Associated Types

type Rep (BackendUpdate pgKind v) :: Type -> Type #

Methods

from :: BackendUpdate pgKind v -> Rep (BackendUpdate pgKind v) x #

to :: Rep (BackendUpdate pgKind v) x -> BackendUpdate pgKind v #

type Rep (BackendUpdate pgKind v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

type Rep (BackendUpdate pgKind v) = D1 ('MetaData "BackendUpdate" "Hasura.Backends.Postgres.Types.Update" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "BackendUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap PGCol (UpdateOpExpression v)))) :+: C1 ('MetaCons "BackendMultiRowUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [MultiRowUpdate pgKind v])))

isEmpty :: BackendUpdate pgKind v -> Bool Source #

Are we updating anything?

data UpdateOpExpression v Source #

The various update operators supported by PostgreSQL, i.e. the _set, _inc operators that appear in the schema.

See Update Mutations User docs

Instances

Instances details
Functor UpdateOpExpression Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Foldable UpdateOpExpression Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

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

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

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

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

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

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

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

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

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

toList :: UpdateOpExpression a -> [a] #

null :: UpdateOpExpression a -> Bool #

length :: UpdateOpExpression a -> Int #

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

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

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

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

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

Traversable UpdateOpExpression Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Eq v => Eq (UpdateOpExpression v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Data v => Data (UpdateOpExpression v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Methods

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

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

toConstr :: UpdateOpExpression v -> Constr #

dataTypeOf :: UpdateOpExpression v -> DataType #

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

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

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

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

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

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

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

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

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

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

Show v => Show (UpdateOpExpression v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Generic (UpdateOpExpression v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update

Associated Types

type Rep (UpdateOpExpression v) :: Type -> Type #

type Rep (UpdateOpExpression v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.Types.Update