napkin-0.5.11
Copyright(c) Soostone Inc 2020
LicenseAllRightsReserved
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Napkin.Spec.Types

Description

 
Synopsis

Documentation

data SpecRuntime b #

Constructors

SpecRuntime 

newtype CustomValidator #

CustomValidators are run before namespacing and return a list of errors in the incoming Spec.

TODO. I find this outmoded - it's a very restrictive form of doing custom validations. The new effect machinery is much richer in being able to introspect different types of database interactions under the SqlBackend type. Keeping this for legacy compatibility for now.

Instances

Instances details
Default CustomValidator # 
Instance details

Defined in Napkin.Spec.Types

newtype Spec b a #

Constructors

Spec 

Fields

Instances

Instances details
Monad (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

(>>=) :: Spec b a -> (a -> Spec b b0) -> Spec b b0 #

(>>) :: Spec b a -> Spec b b0 -> Spec b b0 #

return :: a -> Spec b a #

Functor (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

fmap :: (a -> b0) -> Spec b a -> Spec b b0 #

(<$) :: a -> Spec b b0 -> Spec b a #

Applicative (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

pure :: a -> Spec b a #

(<*>) :: Spec b (a -> b0) -> Spec b a -> Spec b b0 #

liftA2 :: (a -> b0 -> c) -> Spec b a -> Spec b b0 -> Spec b c #

(*>) :: Spec b a -> Spec b b0 -> Spec b b0 #

(<*) :: Spec b a -> Spec b b0 -> Spec b a #

MonadIO (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

liftIO :: IO a -> Spec b a #

MonadThrow (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

throwM :: Exception e => e -> Spec b a #

MonadCatch (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

catch :: Exception e => Spec b a -> (e -> Spec b a) -> Spec b a #

MonadMask (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

mask :: ((forall a. Spec b a -> Spec b a) -> Spec b b0) -> Spec b b0 #

uninterruptibleMask :: ((forall a. Spec b a -> Spec b a) -> Spec b b0) -> Spec b b0 #

generalBracket :: Spec b a -> (a -> ExitCase b0 -> Spec b c) -> (a -> Spec b b0) -> Spec b (b0, c) #

MonadState (Specs b) (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

get :: Spec b (Specs b) #

put :: Specs b -> Spec b () #

state :: (Specs b -> (a, Specs b)) -> Spec b a #

data Specs b #

Constructors

Specs 

Fields

Instances

Instances details
Generic (Specs b) # 
Instance details

Defined in Napkin.Spec.Types

Associated Types

type Rep (Specs b) :: Type -> Type #

Methods

from :: Specs b -> Rep (Specs b) x #

to :: Rep (Specs b) x -> Specs b #

Default (Specs b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

def :: Specs b #

MonadState (Specs b) (Spec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

get :: Spec b (Specs b) #

put :: Specs b -> Spec b () #

state :: (Specs b -> (a, Specs b)) -> Spec b a #

type Rep (Specs b) # 
Instance details

Defined in Napkin.Spec.Types

type Rep (Specs b) = D1 ('MetaData "Specs" "Napkin.Spec.Types" "napkin-0.5.11-LzNtVzWpCFCrZQk4T3eyK" 'False) (C1 ('MetaCons "Specs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_specsTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecTableMap b)) :*: S1 ('MetaSel ('Just "_specsHooks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([Ref Table], HookProgram b)])) :*: (S1 ('MetaSel ('Just "_specsMetaArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SpecMetaArgs) :*: S1 ('MetaSel ('Just "_specsTransformer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QueryTransformer))))

data UpdateStrategy #

Each strategy acts independently. For example, if you have only UpdateWithDependency, it wouldn't update even if the table were missing. You need to specify each strategy in the list.

Instances

Instances details
Eq UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

Data UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: UpdateStrategy -> Constr #

dataTypeOf :: UpdateStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

Show UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

Generic UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

Associated Types

type Rep UpdateStrategy :: Type -> Type #

ToJSON UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Yaml.Types

FromJSON UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Yaml.Types

type Rep UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types

type Rep UpdateStrategy = D1 ('MetaData "UpdateStrategy" "Napkin.Spec.Types" "napkin-0.5.11-LzNtVzWpCFCrZQk4T3eyK" 'False) ((C1 ('MetaCons "UpdateAlways" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpdatePeriodically" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime))) :+: (C1 ('MetaCons "UpdateWithDependency" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpdateIfMissing" 'PrefixI 'False) (U1 :: Type -> Type)))

data TableSpec b #

Constructors

TableSpec 

Fields

Instances

Instances details
ToJSON (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types

ToObject (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

toObject :: TableSpec b -> Object #

LogItem (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types

AsRelation (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types

TableRef (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

tableRef :: Lens' (TableSpec b) (Ref Table) #

data SpecTarget #

Constructors

SpecTable 
SpecView 

Instances

Instances details
Eq SpecTarget # 
Instance details

Defined in Napkin.Spec.Types

Data SpecTarget # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: SpecTarget -> Constr #

dataTypeOf :: SpecTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpecTarget # 
Instance details

Defined in Napkin.Spec.Types

newtype Showing a #

Constructors

Showing 

Fields

Instances

Instances details
(Show a, HasSqlValueSyntax bk Text) => HasSqlValueSyntax bk (Showing a) # 
Instance details

Defined in Napkin.Metadata.Instances

Methods

sqlValueSyntax :: Showing a -> bk #

(Read a, BeamMigrateSqlBackend bk, FromBackendRow bk Text) => FromBackendRow bk (Showing a) # 
Instance details

Defined in Napkin.Metadata.Instances

BeamMigrateSqlBackend bk => HasDefaultSqlDataType bk (Showing a) # 
Instance details

Defined in Napkin.Metadata.Instances

Eq a => Eq (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

Methods

(==) :: Showing a -> Showing a -> Bool #

(/=) :: Showing a -> Showing a -> Bool #

Data a => Data (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: Showing a -> Constr #

dataTypeOf :: Showing a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

Methods

compare :: Showing a -> Showing a -> Ordering #

(<) :: Showing a -> Showing a -> Bool #

(<=) :: Showing a -> Showing a -> Bool #

(>) :: Showing a -> Showing a -> Bool #

(>=) :: Showing a -> Showing a -> Bool #

max :: Showing a -> Showing a -> Showing a #

min :: Showing a -> Showing a -> Showing a #

Read a => Read (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

Show a => Show (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

Methods

showsPrec :: Int -> Showing a -> ShowS #

show :: Showing a -> String #

showList :: [Showing a] -> ShowS #

Show a => ToJSON (Showing a) # 
Instance details

Defined in Napkin.Spec.Types

newtype Pipeline #

A namespace for a given pipeline

Constructors

Pipeline 

Fields

Instances

Instances details
Eq Pipeline # 
Instance details

Defined in Napkin.Spec.Types

Data Pipeline # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: Pipeline -> Constr #

dataTypeOf :: Pipeline -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Pipeline # 
Instance details

Defined in Napkin.Spec.Types

Show Pipeline # 
Instance details

Defined in Napkin.Spec.Types

IsString Pipeline # 
Instance details

Defined in Napkin.Spec.Types

Generic Pipeline # 
Instance details

Defined in Napkin.Spec.Types

Associated Types

type Rep Pipeline :: Type -> Type #

Methods

from :: Pipeline -> Rep Pipeline x #

to :: Rep Pipeline x -> Pipeline #

ToJSON Pipeline # 
Instance details

Defined in Napkin.Spec.Types

FromJSON Pipeline # 
Instance details

Defined in Napkin.Spec.Types

BeamSqlBackend bk => HasSqlEqualityCheck bk Pipeline # 
Instance details

Defined in Napkin.Metadata.Instances

HasSqlValueSyntax bk Text => HasSqlValueSyntax bk Pipeline # 
Instance details

Defined in Napkin.Metadata.Instances

Methods

sqlValueSyntax :: Pipeline -> bk #

(BeamMigrateSqlBackend bk, FromBackendRow bk Text) => FromBackendRow bk Pipeline # 
Instance details

Defined in Napkin.Metadata.Instances

BeamMigrateSqlBackend bk => HasDefaultSqlDataType bk Pipeline # 
Instance details

Defined in Napkin.Metadata.Instances

type Rep Pipeline # 
Instance details

Defined in Napkin.Spec.Types

type Rep Pipeline = D1 ('MetaData "Pipeline" "Napkin.Spec.Types" "napkin-0.5.11-LzNtVzWpCFCrZQk4T3eyK" 'True) (C1 ('MetaCons "Pipeline" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unPipeline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype AppName #

Constructors

AppName 

Fields

Instances

Instances details
Eq AppName # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

Data AppName # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: AppName -> Constr #

dataTypeOf :: AppName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AppName # 
Instance details

Defined in Napkin.Spec.Types

Show AppName # 
Instance details

Defined in Napkin.Spec.Types

Generic AppName # 
Instance details

Defined in Napkin.Spec.Types

Associated Types

type Rep AppName :: Type -> Type #

Methods

from :: AppName -> Rep AppName x #

to :: Rep AppName x -> AppName #

Semigroup AppName # 
Instance details

Defined in Napkin.Spec.Types

ToJSON AppName # 
Instance details

Defined in Napkin.Spec.Types

FromJSON AppName # 
Instance details

Defined in Napkin.Spec.Types

BeamSqlBackend bk => HasSqlEqualityCheck bk AppName # 
Instance details

Defined in Napkin.Metadata.Instances

HasSqlValueSyntax bk Text => HasSqlValueSyntax bk AppName # 
Instance details

Defined in Napkin.Metadata.Instances

Methods

sqlValueSyntax :: AppName -> bk #

(BeamMigrateSqlBackend bk, FromBackendRow bk Text) => FromBackendRow bk AppName # 
Instance details

Defined in Napkin.Metadata.Instances

BeamMigrateSqlBackend bk => HasDefaultSqlDataType bk AppName # 
Instance details

Defined in Napkin.Metadata.Instances

HasAppName OAuth2CorrelatedKey (Maybe AppName) # 
Instance details

Defined in Napkin.Auth.Types

type Rep AppName # 
Instance details

Defined in Napkin.Spec.Types

type Rep AppName = D1 ('MetaData "AppName" "Napkin.Spec.Types" "napkin-0.5.11-LzNtVzWpCFCrZQk4T3eyK" 'True) (C1 ('MetaCons "AppName" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unAppName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

pattern NapkinTablePrefix :: (Eq a, IsString a) => a #

runSpec :: Spec b a -> IO (Specs b) #

runSpecE :: ExceptT e (Spec b) a -> IO (Either e (Specs b)) #

unShowing :: forall a a. Iso (Showing a) (Showing a) a a #

specAction :: forall b. Lens' (TableSpec b) (SpecProgram b) #

specGrants :: forall b. Lens' (TableSpec b) [([Privilege], [Actor])] #

specTable :: forall b. Lens' (TableSpec b) (Ref Table) #

data CreateTableAs b #

Instances

Instances details
IsBackendTableMeta b => Eq (CreateTableAs b) # 
Instance details

Defined in Napkin.Spec.Types

(IsBackendTableMeta b, Data (BackendTableMeta b), Typeable (BackendTableMeta b), Typeable b, Data b) => Data (CreateTableAs b) # 
Instance details

Defined in Napkin.Spec.Types

Methods

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

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

toConstr :: CreateTableAs b -> Constr #

dataTypeOf :: CreateTableAs b -> DataType #

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

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

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

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

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

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

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

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

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

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

IsBackendTableMeta b => Show (CreateTableAs b) # 
Instance details

Defined in Napkin.Spec.Types

MaybeQuery (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types

HasDefinition (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types

AsRelation (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types

TableRef (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types

HasDeps (CreateTableAs m) # 
Instance details

Defined in Napkin.Spec.Types

specsHooks :: forall b. Lens' (Specs b) [([Ref Table], HookProgram b)] #

specsTables :: forall b. Lens' (Specs b) (SpecTableMap b) #

allSpecsTables :: Specs b -> Set (Ref Table) #

All tables that are being created/managed as part of this spec.

namespaceManagedTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b #

Rename all napkin-managed tables in the `Specs b`.

namespaceUnmanagedTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b #

Rename all unmanaged tables in the `Specs b`.

namespaceSomeTables :: forall b. (Ref Table -> Bool) -> (Ref Table -> Ref Table) -> Specs b -> Specs b #

Rename some tables in the `Specs b`.

namespaceAllTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b #

Apply a renamer to all tables in the `Specs b` (managed or unmanaged).

namespaceFunctions :: forall b. (Ref Function -> Ref Function) -> Specs b -> Specs b #

setAllTableGrants :: MonadState (Specs b) m => [([Privilege], [Actor])] -> m () #

Set the same Grant permissions for all tables defined in the spec at once. Convenience function for a common use case. Acts monadically, so it will apply to all specs so far defined in the Spec block.

ctaName :: forall b. Lens' (CreateTableAs b) (Ref Table) #

type SpecProgram b = SpecProgram' b () #

type HookProgram b = HookProgram' b () #

Hooks have different cabapilities than specs