Copyright | (c) Soostone Inc 2020 |
---|---|
License | AllRightsReserved |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data SpecRuntime b = SpecRuntime {
- _spPipeline :: Pipeline
- _spConn :: BackendConn b
- type SpecPreprocessorFunc bk = SpecMetaArgs -> Specs bk -> Specs bk
- type SpecPreprocessor b = Sem [Input MetaArguments, State (Specs b), FatalError, Embed IO, Log] ()
- newtype SpecPreprocessorWithArgParser b = SpecPreprocessorWithArgParser (Object -> Parser (SpecPreprocessor b))
- newtype ExternMacros = ExternMacros (Map (Ref Function) (ExternFun -> SExp))
- newtype CustomValidator = CustomValidator (SpecMetaArgs -> Ref Table -> Maybe FilePath -> Query -> [Text])
- newtype Spec b a = Spec {}
- data Specs b = Specs {
- _specsTables :: SpecTableMap b
- _specsHooks :: [([Ref Table], HookProgram b)]
- _specsMetaArgs :: SpecMetaArgs
- _specsTransformer :: QueryTransformer
- type SpecMetaArgs = Map Text Value
- type SpecTableMap b = Map (Ref Table) (TableSpec b)
- data UpdateStrategy
- type TableSpecTag = String
- data TableSpec b = TableSpec {
- _specTable :: Ref Table
- _specAction :: SpecProgram b
- _specPreHooks :: [HookProgram b]
- _specPostHooks :: [HookProgram b]
- _specUpdate :: [UpdateStrategy]
- _specGrants :: [([Privilege], [Actor])]
- _specTags :: [TableSpecTag]
- data SpecTarget
- newtype Showing a = Showing {
- _unShowing :: a
- type DepChain = Map (Ref Table) UTCTime
- newtype Pipeline = Pipeline {
- _unPipeline :: Text
- newtype AppName = AppName {
- _unAppName :: Text
- pattern NapkinTablePrefix :: (Eq a, IsString a) => a
- isTemporaryTable :: Ref Table -> Bool
- 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])]
- specPostHooks :: forall b. Lens' (TableSpec b) [HookProgram b]
- specPreHooks :: forall b. Lens' (TableSpec b) [HookProgram b]
- specTable :: forall b. Lens' (TableSpec b) (Ref Table)
- specTags :: forall b. Lens' (TableSpec b) [TableSpecTag]
- specUpdate :: forall b. Lens' (TableSpec b) [UpdateStrategy]
- data CreateTableAs b = CreateTableAs {}
- specsHooks :: forall b. Lens' (Specs b) [([Ref Table], HookProgram b)]
- specsMetaArgs :: forall b. Lens' (Specs b) SpecMetaArgs
- specsTables :: forall b. Lens' (Specs b) (SpecTableMap b)
- specsTransformer :: forall b. Lens' (Specs b) QueryTransformer
- allSpecsTables :: Specs b -> [Ref Table]
- namespaceManagedTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b
- namespaceUnmanagedTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b
- namespaceSomeTables :: forall b. (Ref Table -> Bool) -> (Ref Table -> Ref Table) -> Specs b -> Specs b
- namespaceAllTables :: forall b. (Ref Table -> Ref Table) -> Specs b -> Specs b
- namespaceFunctions :: forall b. (Ref Function -> Ref Function) -> Specs b -> Specs b
- setAllTableGrants :: MonadState (Specs b) m => [([Privilege], [Actor])] -> m ()
- prettyQueryStats :: QueryStats -> String
- prettyBytes :: Int64 -> String
- ctaMeta :: forall b b. Lens (CreateTableAs b) (CreateTableAs b) (BackendTableMeta b) (BackendTableMeta b)
- ctaName :: forall b. Lens' (CreateTableAs b) (Ref Table)
- ctaQuery :: forall b. Lens' (CreateTableAs b) Query
- type SpecProgram b = SemSpec b ()
- type HookProgram b = SemHook b ()
- type IsBackendTableMeta b = IsBackendTableMeta' (BackendTableMeta b)
Documentation
data SpecRuntime b #
SpecRuntime | |
|
type SpecPreprocessorFunc bk = SpecMetaArgs -> Specs bk -> Specs bk #
type SpecPreprocessor b = Sem [Input MetaArguments, State (Specs b), FatalError, Embed IO, Log] () #
newtype SpecPreprocessorWithArgParser b #
newtype ExternMacros #
Instances
IsList ExternMacros # | |
Defined in Napkin.Spec.Types type Item ExternMacros # fromList :: [Item ExternMacros] -> ExternMacros # fromListN :: Int -> [Item ExternMacros] -> ExternMacros # toList :: ExternMacros -> [Item ExternMacros] # | |
Semigroup ExternMacros # | |
Defined in Napkin.Spec.Types (<>) :: ExternMacros -> ExternMacros -> ExternMacros # sconcat :: NonEmpty ExternMacros -> ExternMacros # stimes :: Integral b => b -> ExternMacros -> ExternMacros # | |
Monoid ExternMacros # | |
Defined in Napkin.Spec.Types mempty :: ExternMacros # mappend :: ExternMacros -> ExternMacros -> ExternMacros # mconcat :: [ExternMacros] -> ExternMacros # | |
Default ExternMacros # | |
Defined in Napkin.Spec.Types def :: ExternMacros # | |
type Item ExternMacros # | |
Defined in Napkin.Spec.Types |
newtype CustomValidator #
CustomValidator
s 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.
CustomValidator (SpecMetaArgs -> Ref Table -> Maybe FilePath -> Query -> [Text]) |
Instances
Default CustomValidator # | |
Defined in Napkin.Spec.Types def :: CustomValidator # |
Instances
Monad (Spec b) # | |
Functor (Spec b) # | |
Applicative (Spec b) # | |
MonadIO (Spec b) # | |
Defined in Napkin.Spec.Types | |
MonadThrow (Spec b) # | |
Defined in Napkin.Spec.Types | |
MonadCatch (Spec b) # | |
MonadMask (Spec b) # | |
MonadState (Specs b) (Spec b) # | |
Specs | |
|
Instances
Generic (Specs b) # | |
Default (Specs b) # | |
Defined in Napkin.Spec.Types | |
MonadState (Specs b) (Spec b) # | |
type Rep (Specs b) # | |
Defined in Napkin.Spec.Types type Rep (Specs b) = D1 ('MetaData "Specs" "Napkin.Spec.Types" "napkin-0.5.10-C0Hygrce3goLKcQ6g1wIUX" '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)))) |
type SpecMetaArgs = Map Text Value #
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
type TableSpecTag = String #
TableSpec | |
|
Instances
ToJSON (TableSpec b) # | |
Defined in Napkin.Spec.Types | |
ToObject (TableSpec b) # | |
Defined in Napkin.Spec.Types | |
LogItem (TableSpec b) # | |
Defined in Napkin.Spec.Types payloadKeys :: Verbosity -> TableSpec b -> PayloadSelection # | |
AsRelation (TableSpec b) # | |
Defined in Napkin.Spec.Types asRelation :: TableSpec b -> Relation # | |
TableRef (TableSpec b) # | |
data SpecTarget #
Instances
Eq SpecTarget # | |
Defined in Napkin.Spec.Types (==) :: SpecTarget -> SpecTarget -> Bool # (/=) :: SpecTarget -> SpecTarget -> Bool # | |
Data SpecTarget # | |
Defined in Napkin.Spec.Types 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 # | |
Defined in Napkin.Spec.Types showsPrec :: Int -> SpecTarget -> ShowS # show :: SpecTarget -> String # showList :: [SpecTarget] -> ShowS # |
Showing | |
|
Instances
(Show a, HasSqlValueSyntax bk Text) => HasSqlValueSyntax bk (Showing a) # | |
Defined in Napkin.Metadata.Instances sqlValueSyntax :: Showing a -> bk # | |
(Read a, BeamMigrateSqlBackend bk, FromBackendRow bk Text) => FromBackendRow bk (Showing a) # | |
Defined in Napkin.Metadata.Instances fromBackendRow :: FromBackendRowM bk (Showing a) # | |
BeamMigrateSqlBackend bk => HasDefaultSqlDataType bk (Showing a) # | |
Defined in Napkin.Metadata.Instances defaultSqlDataType :: Proxy (Showing a) -> Proxy bk -> Bool -> BeamSqlBackendDataTypeSyntax bk # defaultSqlDataTypeConstraints :: Proxy (Showing a) -> Proxy bk -> Bool -> [FieldCheck] # | |
Eq a => Eq (Showing a) # | |
Data a => Data (Showing a) # | |
Defined in Napkin.Spec.Types 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) # | |
Defined in Napkin.Spec.Types | |
Read a => Read (Showing a) # | |
Show a => Show (Showing a) # | |
Show a => ToJSON (Showing a) # | |
Defined in Napkin.Spec.Types |
A namespace for a given pipeline
Instances
Instances
pattern NapkinTablePrefix :: (Eq a, IsString a) => a #
isTemporaryTable :: Ref Table -> Bool #
specAction :: forall b. Lens' (TableSpec b) (SpecProgram b) #
specPostHooks :: forall b. Lens' (TableSpec b) [HookProgram b] #
specPreHooks :: forall b. Lens' (TableSpec b) [HookProgram b] #
specTags :: forall b. Lens' (TableSpec b) [TableSpecTag] #
specUpdate :: forall b. Lens' (TableSpec b) [UpdateStrategy] #
data CreateTableAs b #
Instances
specsHooks :: forall b. Lens' (Specs b) [([Ref Table], HookProgram b)] #
specsMetaArgs :: forall b. Lens' (Specs b) SpecMetaArgs #
specsTables :: forall b. Lens' (Specs b) (SpecTableMap b) #
specsTransformer :: forall b. Lens' (Specs b) QueryTransformer #
allSpecsTables :: Specs b -> [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).
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.
prettyQueryStats :: QueryStats -> String #
prettyBytes :: Int64 -> String #
ctaMeta :: forall b b. Lens (CreateTableAs b) (CreateTableAs b) (BackendTableMeta b) (BackendTableMeta b) #
ctaQuery :: forall b. Lens' (CreateTableAs b) Query #
type SpecProgram b = SemSpec b () #
type HookProgram b = SemHook b () #
Hooks have different cabapilities than specs
type IsBackendTableMeta b = IsBackendTableMeta' (BackendTableMeta b) #