napkin-spec-2.0.0
Safe HaskellNone
LanguageGHC2024

Napkin.Spec.Types.Spec

Synopsis

Documentation

data TableSpec b #

Constructors

TableSpec 

Fields

Instances

Instances details
ToJSON (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Generic (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Associated Types

type Rep (TableSpec b) 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

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

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

LogItem (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

ToObject (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

toObject :: TableSpec b -> Object #

type Rep (TableSpec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

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
Data UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

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 #

Generic UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

Associated Types

type Rep UpdateStrategy 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep UpdateStrategy = D1 ('MetaData "UpdateStrategy" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" '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) :+: C1 ('MetaCons "UpdateIfErroredLastRun" 'PrefixI 'False) (U1 :: Type -> Type))))
Show UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

Eq UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

Ord UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep UpdateStrategy # 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep UpdateStrategy = D1 ('MetaData "UpdateStrategy" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" '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) :+: C1 ('MetaCons "UpdateIfErroredLastRun" 'PrefixI 'False) (U1 :: Type -> Type))))

data SpecGlobalHook b #

Instances

Instances details
Generic b => Generic (SpecGlobalHook b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Associated Types

type Rep (SpecGlobalHook b) 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep (SpecGlobalHook b) = D1 ('MetaData "SpecGlobalHook" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "PureSpecGlobalHook" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PureGlobalHookProgram b))) :+: C1 ('MetaCons "IOSpecGlobalHook" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IOGlobalHookProgram b))))
type Rep (SpecGlobalHook b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep (SpecGlobalHook b) = D1 ('MetaData "SpecGlobalHook" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "PureSpecGlobalHook" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PureGlobalHookProgram b))) :+: C1 ('MetaCons "IOSpecGlobalHook" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IOGlobalHookProgram b))))

data Specs b #

Constructors

Specs 

Fields

Instances

Instances details
Default (Specs b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

def :: Specs b #

Generic (Specs b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Associated Types

type Rep (Specs b) 
Instance details

Defined in Napkin.Spec.Types.Spec

type Rep (Specs b) = D1 ('MetaData "Specs" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "Specs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecTableMap b)) :*: S1 ('MetaSel ('Just "hooks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GlobalHooks b))) :*: (S1 ('MetaSel ('Just "metaArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SpecMetaArgs) :*: S1 ('MetaSel ('Just "transformer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QueryTransformer))))

Methods

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

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

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

Defined in Napkin.Spec.Types.Spec

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.Spec

type Rep (Specs b) = D1 ('MetaData "Specs" "Napkin.Spec.Types.Spec" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "Specs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecTableMap b)) :*: S1 ('MetaSel ('Just "hooks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GlobalHooks b))) :*: (S1 ('MetaSel ('Just "metaArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SpecMetaArgs) :*: S1 ('MetaSel ('Just "transformer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QueryTransformer))))

newtype Spec b a #

Constructors

Spec 

Fields

Instances

Instances details
MonadReader SpecPaths (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

ask :: Spec b SpecPaths #

local :: (SpecPaths -> SpecPaths) -> Spec b a -> Spec b a #

reader :: (SpecPaths -> a) -> Spec b a #

MonadIO (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

liftIO :: IO a -> Spec b a #

MonadCatch (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

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

MonadMask (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

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

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

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

MonadThrow (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

throwM :: (HasCallStack, Exception e) => e -> Spec b a #

Applicative (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

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 #

Functor (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

Methods

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

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

Monad (Spec b) # 
Instance details

Defined in Napkin.Spec.Types.Spec

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 #

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

Defined in Napkin.Spec.Types.Spec

Methods

get :: Spec b (Specs b) #

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

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

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.Spec

type SpecPreprocessor b = Sem '[Input SpecPaths :: (Type -> Type) -> Type -> Type, Input MetaArguments :: (Type -> Type) -> Type -> Type, State (Specs b) :: (Type -> Type) -> Type -> Type, Output DepsValidator :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Embed IO, Log :: (Type -> Type) -> Type -> Type] () #

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

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

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

allSpecsTables :: Specs b -> Set SpecTableName #

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

specTable :: forall b f. Functor f => (SpecTableName -> f SpecTableName) -> TableSpec b -> f (TableSpec b) #

specAction :: forall b f. Functor f => (SpecProgram b -> f (SpecProgram b)) -> TableSpec b -> f (TableSpec b) #

specUpdate :: forall b f. Functor f => ([UpdateStrategy] -> f [UpdateStrategy]) -> TableSpec b -> f (TableSpec b) #

specTags :: forall b f. Functor f => (Set TableSpecTag -> f (Set TableSpecTag)) -> TableSpec b -> f (TableSpec b) #

specsTables :: forall b f. Functor f => (SpecTableMap b -> f (SpecTableMap b)) -> Specs b -> f (Specs b) #

specsHooks :: forall b f. Functor f => (GlobalHooks b -> f (GlobalHooks b)) -> Specs b -> f (Specs b) #

specsMetaArgs :: forall b f. Functor f => (SpecMetaArgs -> f SpecMetaArgs) -> Specs b -> f (Specs b) #

specsTransformer :: forall b f. Functor f => (QueryTransformer -> f QueryTransformer) -> Specs b -> f (Specs b) #

specTagRefMap :: [TableSpec b] -> Map (Maybe TableSpecTag) [SpecTableName] #

create a mapping of TableSpecTags to `Ref Table`s for dumping.

specListTags :: forall bk m. MonadIO m => Specs bk -> m () #

Print the result of specTagRefMap'ing a particular spec to terminal.

Orphan instances

Buildable SpecDependency # 
Instance details