napkin-api-2.0.0
Safe HaskellNone
LanguageGHC2024

Napkin.Run.Effects

Synopsis

Documentation

describe :: forall (r :: EffectRow) a. Members '[Assertion :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r a -> Sem r a #

assert :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> AssertionStatus -> Sem r () #

assertError :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Sem ((Error Text :: (Type -> Type) -> Type -> Type) ': r) () -> Sem r () #

data AssertionStatus #

Constructors

Success 
Failure (Maybe Text) 

Instances

Instances details
ToJSON AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Generic AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Associated Types

type Rep AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

type Rep AssertionStatus = D1 ('MetaData "AssertionStatus" "Napkin.Run.Effects.Languages.Assertion" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Failure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))
Show AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Eq AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

type Rep AssertionStatus 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

type Rep AssertionStatus = D1 ('MetaData "AssertionStatus" "Napkin.Run.Effects.Languages.Assertion" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Failure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data Assertion (m :: k) a #

Assertion effects so we can skip past them in dry runs, and optionally throw exceptions or just collect them along the way for final reporting, etc..

Instances

Instances details
ToDumpItem (b :: k) (Assertion :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. Assertion (Sem r) x -> DumpItem b #

GShow (Assertion a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Methods

gshowsPrec :: Int -> Assertion a a0 -> ShowS #

Show (Assertion a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Methods

showsPrec :: Int -> Assertion a b -> ShowS #

show :: Assertion a b -> String #

showList :: [Assertion a b] -> ShowS #

Eq (Assertion a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.Assertion

Methods

(==) :: Assertion a b -> Assertion a b -> Bool #

(/=) :: Assertion a b -> Assertion a b -> Bool #

getCurrentTime :: forall (effs :: EffectRow). Member (Time :: (Type -> Type) -> Type -> Type) effs => Sem effs UTCTime #

data External (m :: k) a #

Instances

Instances details
ToDumpItem (b :: k) (External :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. External (Sem r) x -> DumpItem b #

GEq (External a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.External

Methods

geq :: External a a0 -> External a b -> Maybe (a0 :~: b) #

GShow (External t :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.External

Methods

gshowsPrec :: Int -> External t a -> ShowS #

Show (External m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.External

Methods

showsPrec :: Int -> External m a -> ShowS #

show :: External m a -> String #

showList :: [External m a] -> ShowS #

Eq (External m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.External

Methods

(==) :: External m a -> External m a -> Bool #

(/=) :: External m a -> External m a -> Bool #

dropView :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> MissingBehavior -> Cascade -> Sem r () #

assertM :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Sem r AssertionStatus -> Sem r () #

logInfo :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

addDependency :: forall (r :: EffectRow). Member (Output ExtraDependencies :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r () #

Add the given reference to list of dependency for the underlying region.

Later during interpretation, this will cause the given dependency to be forcefully considered upstream dependency within the enclosed region even though they were not seen in the parsed SQL.

getAnnotations :: forall {k} (b :: k) (r :: EffectRow). Member (AnnotateRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r TableAnnotations #

type Time = Input UTCTime :: k1 -> Type -> Type #

logError :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logDebug :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

renderQuery :: forall (r :: EffectRow). Member (SqlRender :: (Type -> Type) -> Type -> Type) r => Query -> Sem r SqlText #

checkTableExists :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r Bool #

renameTable :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Ref Table -> Sem r () #

newtype RandomToken #

Constructors

RandomToken 

Fields

type family Members (es :: [Effect]) (r :: EffectRow) where ... #

Makes constraints of functions that use multiple effects shorter by translating single list of effects into multiple Member constraints:

foo :: Members '[ Output Int
                , Output Bool
                , State String
                ] r
    => Sem r ()

translates into:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       , Member (State String) r
       )
    => Sem r ()

Since: polysemy-0.1.2.0

Equations

Members ('[] :: [Effect]) r = () 
Members (e ': es) r = (Member e r, Members es r) 

data Sem (r :: EffectRow) a #

The Sem monad handles computations of arbitrary extensible effects. A value of type Sem r describes a program with the capabilities of r. For best results, r should always be kept polymorphic, but you can add capabilities via the Member constraint.

The value of the Sem monad is that it allows you to write programs against a set of effects without a predefined meaning, and provide that meaning later. For example, unlike with mtl, you can decide to interpret an Error effect traditionally as an Either, or instead as (a significantly faster) IO Exception. These interpretations (and others that you might add) may be used interchangeably without needing to write any newtypes or Monad instances. The only change needed to swap interpretations is to change a call from runError to errorToIOFinal.

The effect stack r can contain arbitrary other monads inside of it. These monads are lifted into effects via the Embed effect. Monadic values can be lifted into a Sem via embed.

Higher-order actions of another monad can be lifted into higher-order actions of Sem via the Final effect, which is more powerful than Embed, but also less flexible to interpret.

A Sem can be interpreted as a pure value (via run) or as any traditional Monad (via runM or runFinal). Each effect E comes equipped with some interpreters of the form:

runE :: Sem (E ': r) a -> Sem r a

which is responsible for removing the effect E from the effect stack. It is the order in which you call the interpreters that determines the monomorphic representation of the r parameter.

Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:

>>> :{
  example :: Members '[State String, Error String] r => Sem r String
  example = do
    put "start"
    let throwing, catching :: Members '[State String, Error String] r => Sem r String
        throwing = do
          modify (++"-throw")
          throw "error"
          get
        catching = do
          modify (++"-catch")
          get
    catch @String throwing (\ _ -> catching)
:}

when handling Error first, state is preserved after error occurs:

>>> :{
  example
    & runError
    & fmap (either id id)
    & evalState ""
    & runM
    & (print =<<)
:}
"start-throw-catch"

while handling State first discards state in such cases:

>>> :{
  example
    & evalState ""
    & runError
    & fmap (either id id)
    & runM
    & (print =<<)
:}
"start-catch"

A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.

After all of your effects are handled, you'll be left with either a Sem '[] a, a Sem '[ Embed m ] a, or a Sem '[ Final m ] a value, which can be consumed respectively by run, runM, and runFinal.

Examples

As an example of keeping r polymorphic, we can consider the type

Member (State String) r => Sem r ()

to be a program with access to

get :: Sem r String
put :: String -> Sem r ()

methods.

By also adding a

Member (Error Bool) r

constraint on r, we gain access to the

throw :: Bool -> Sem r a
catch :: Sem r a -> (Bool -> Sem r a) -> Sem r a

functions as well.

In this sense, a Member (State s) r constraint is analogous to mtl's MonadState s m and should be thought of as such. However, unlike mtl, a Sem monad may have an arbitrary number of the same effect.

For example, we can write a Sem program which can output either Ints or Bools:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       )
    => Sem r ()
foo = do
  output @Int  5
  output True

Notice that we must use -XTypeApplications to specify that we'd like to use the (Output Int) effect.

Since: polysemy-0.1.2.0

Instances

Instances details
Member (Embed IO) r => MonadIO (Sem r)

This instance will only lift IO actions. If you want to lift into some other MonadIO type, use this instance, and handle it via the embedToMonadIO interpretation.

Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Sem r a #

Member NonDet r => Alternative (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

empty :: Sem r a #

(<|>) :: Sem r a -> Sem r a -> Sem r a #

some :: Sem r a -> Sem r [a] #

many :: Sem r a -> Sem r [a] #

Applicative (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

pure :: a -> Sem f a #

(<*>) :: Sem f (a -> b) -> Sem f a -> Sem f b #

liftA2 :: (a -> b -> c) -> Sem f a -> Sem f b -> Sem f c #

(*>) :: Sem f a -> Sem f b -> Sem f b #

(<*) :: Sem f a -> Sem f b -> Sem f a #

Functor (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

fmap :: (a -> b) -> Sem f a -> Sem f b #

(<$) :: a -> Sem f b -> Sem f a #

Monad (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

(>>=) :: Sem f a -> (a -> Sem f b) -> Sem f b #

(>>) :: Sem f a -> Sem f b -> Sem f b #

return :: a -> Sem f a #

Member NonDet r => MonadPlus (Sem r)

Since: polysemy-0.2.1.0

Instance details

Defined in Polysemy.Internal

Methods

mzero :: Sem r a #

mplus :: Sem r a -> Sem r a -> Sem r a #

Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r)

Since: polysemy-1.1.0.0

Instance details

Defined in Polysemy.Internal

Methods

fail :: String -> Sem r a #

Member Fixpoint r => MonadFix (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

mfix :: (a -> Sem r a) -> Sem r a #

Monoid a => Monoid (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

mempty :: Sem f a #

mappend :: Sem f a -> Sem f a -> Sem f a #

mconcat :: [Sem f a] -> Sem f a #

Semigroup a => Semigroup (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

(<>) :: Sem f a -> Sem f a -> Sem f a #

sconcat :: NonEmpty (Sem f a) -> Sem f a #

stimes :: Integral b => b -> Sem f a -> Sem f a #

class Member (t :: Effect) (r :: EffectRow) #

This class indicates that an effect must be present in the caller's stack. It is the main mechanism by which a program defines its effect dependencies.

Minimal complete definition

membership'

Instances

Instances details
Member t z => Member t (_1 ': z) 
Instance details

Defined in Polysemy.Internal.Union

Methods

membership' :: ElemOf t (_1 ': z)

Member t (t ': z) 
Instance details

Defined in Polysemy.Internal.Union

Methods

membership' :: ElemOf t (t ': z)

executeExternalCommand :: forall (effs :: EffectRow). Members '[FatalError :: (Type -> Type) -> Type -> Type, External :: (Type -> Type) -> Type -> Type] effs => ExternalCommand -> Sem effs () #

type Log = Output LogLine :: k -> Type -> Type #

logNotice :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logWarning :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logCritical :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logAlert :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logEmergency :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LText -> Sem effs () #

logDebug' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logInfo' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logNotice' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logWarning' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logError' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logCritical' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logAlert' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

logEmergency' :: forall (effs :: EffectRow). Member (Log :: (Type -> Type) -> Type -> Type) effs => LogItem -> LText -> Sem effs () #

assert' :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => AssertionGroup -> AssertionSeverity -> Text -> AssertionStatus -> Sem r () #

Assertions are run-time checks based on actual results that may be returned by various operations. Dry runs may ignore these failures, but they're respected in real operations.

assertTrue :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Bool -> Sem r () #

assertEquals :: forall a (r :: EffectRow). (Eq a, Member (Assertion :: (Type -> Type) -> Type -> Type) r) => Text -> a -> a -> Sem r () #

assertTrueWith :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Bool -> Text -> Sem r () #

assertTrueWithM :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Bool -> Sem r Text -> Sem r () #

failedAssertion :: forall (r :: EffectRow). Member (Assertion :: (Type -> Type) -> Type -> Type) r => Text -> Sem r () #

warnOnly :: forall (r :: EffectRow) a. Member (Assertion :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r a #

describe' :: forall (r :: EffectRow) a. Members '[Assertion :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => [Text] -> Sem r a -> Sem r a #

data SqlRead (b :: k) (m :: k1) a #

Instances

Instances details
(IsRenderable SExp b, IsRenderable Query b, IsRenderable Text b) => ToDumpItem (b :: k) (SqlRead b :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. SqlRead b (Sem r) x -> DumpItem b #

GShow (SqlRead b m :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

gshowsPrec :: Int -> SqlRead b m a -> ShowS #

Show (SqlRead b m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

showsPrec :: Int -> SqlRead b m a -> ShowS #

show :: SqlRead b m a -> String #

showList :: [SqlRead b m a] -> ShowS #

Eq (SqlRead b m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

(==) :: SqlRead b m a -> SqlRead b m a -> Bool #

(/=) :: SqlRead b m a -> SqlRead b m a -> Bool #

runQuery :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Query -> Sem r [Map Text Value] #

getTableKind :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r TableKind #

runQuerySingleAnswer :: forall {k} (b :: k) a (r :: EffectRow). (Val a, Member (SqlRead b :: (Type -> Type) -> Type -> Type) r) => Query -> Sem r (Maybe a) #

Run a query and pull out the first column from its first row. Meant for queries that return a single result.

getRelationSchema :: forall {k} (b :: k) (r :: EffectRow). Members '[SqlRead b :: (Type -> Type) -> Type -> Type, Input TemporaryTableName :: (Type -> Type) -> Type -> Type] r => Relation -> Sem r [BackendSchemaField b] #

data SqlRender (m :: k) a #

Instances

Instances details
GShow (SqlRender a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRender

Methods

gshowsPrec :: Int -> SqlRender a a0 -> ShowS #

CacheableEffect (SqlRender :: k -> Type -> Type) SqlRenderCacheKey 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRender

Show (SqlRender a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRender

Methods

showsPrec :: Int -> SqlRender a b -> ShowS #

show :: SqlRender a b -> String #

showList :: [SqlRender a b] -> ShowS #

Eq (SqlRender m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRender

Methods

(==) :: SqlRender m a -> SqlRender m a -> Bool #

(/=) :: SqlRender m a -> SqlRender m a -> Bool #

Ord (SqlRender m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRender

Methods

compare :: SqlRender m a -> SqlRender m a -> Ordering #

(<) :: SqlRender m a -> SqlRender m a -> Bool #

(<=) :: SqlRender m a -> SqlRender m a -> Bool #

(>) :: SqlRender m a -> SqlRender m a -> Bool #

(>=) :: SqlRender m a -> SqlRender m a -> Bool #

max :: SqlRender m a -> SqlRender m a -> SqlRender m a #

min :: SqlRender m a -> SqlRender m a -> SqlRender m a #

renderSExp :: forall (r :: EffectRow). Member (SqlRender :: (Type -> Type) -> Type -> Type) r => SExp -> Sem r SqlText #

data SqlParse (m :: k) a #

Instances

Instances details
GShow (SqlParse a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlParse

Methods

gshowsPrec :: Int -> SqlParse a a0 -> ShowS #

CacheableEffect (SqlParse :: k -> Type -> Type) SqlParseCacheKey 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlParse

Show (SqlParse m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlParse

Methods

showsPrec :: Int -> SqlParse m a -> ShowS #

show :: SqlParse m a -> String #

showList :: [SqlParse m a] -> ShowS #

Eq (SqlParse m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlParse

Methods

(==) :: SqlParse m a -> SqlParse m a -> Bool #

(/=) :: SqlParse m a -> SqlParse m a -> Bool #

Ord (SqlParse m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlParse

Methods

compare :: SqlParse m a -> SqlParse m a -> Ordering #

(<) :: SqlParse m a -> SqlParse m a -> Bool #

(<=) :: SqlParse m a -> SqlParse m a -> Bool #

(>) :: SqlParse m a -> SqlParse m a -> Bool #

(>=) :: SqlParse m a -> SqlParse m a -> Bool #

max :: SqlParse m a -> SqlParse m a -> SqlParse m a #

min :: SqlParse m a -> SqlParse m a -> SqlParse m a #

parseSqlQuery :: forall (r :: EffectRow). Members '[SqlParse :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type] r => SourceLocation -> Text -> Sem r Query #

parseSqlExp :: forall (r :: EffectRow). Members '[SqlParse :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type] r => SourceLocation -> Text -> Sem r SExp #

parseStatements :: forall (r :: EffectRow) a. (Members '[SqlParse :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type] r, Stateable a) => SourceLocation -> Text -> Sem r [a] #

overrideDialect :: forall (r :: EffectRow) a. Member (Reader SQLDialect) r => SQLDialect -> Sem r a -> Sem r a #

data LoadQuery (m :: k) a #

Effects that deal with local files

Instances

Instances details
CacheableEffect (LoadQuery :: k -> Type -> Type) LoadQueryCacheKey 
Instance details

Defined in Napkin.Run.Effects.Languages.LoadQuery

Eq (LoadQuery m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.LoadQuery

Methods

(==) :: LoadQuery m a -> LoadQuery m a -> Bool #

(/=) :: LoadQuery m a -> LoadQuery m a -> Bool #

Ord (LoadQuery m a) 
Instance details

Defined in Napkin.Run.Effects.Languages.LoadQuery

Methods

compare :: LoadQuery m a -> LoadQuery m a -> Ordering #

(<) :: LoadQuery m a -> LoadQuery m a -> Bool #

(<=) :: LoadQuery m a -> LoadQuery m a -> Bool #

(>) :: LoadQuery m a -> LoadQuery m a -> Bool #

(>=) :: LoadQuery m a -> LoadQuery m a -> Bool #

max :: LoadQuery m a -> LoadQuery m a -> LoadQuery m a #

min :: LoadQuery m a -> LoadQuery m a -> LoadQuery m a #

loadSqlFile :: forall (r :: EffectRow). Members '[SqlParse :: (Type -> Type) -> Type -> Type, LoadQuery :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type] r => FilePath -> SqlTemplateVariables -> Sem r Query #

data SqlWrite b (m :: k) a #

Instances

Instances details
(Show (BackendTableMeta b), Show (BackendViewMeta b), Show (BackendMaterializedViewMeta b), IsRenderable Query b, IsRenderable Statement b, IsRenderable SExp b, IsRenderable UpdateQuery b, IsRenderable Text b, Default (BackendTableMeta b), Default (BackendViewMeta b), MaybeDefault (YamlBackendMaterializedViewMeta b), Eq (BackendTableMeta b), Eq (BackendViewMeta b), Eq (YamlBackendMaterializedViewMeta b)) => ToDumpItem (b :: Type) (SqlWrite b :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. SqlWrite b (Sem r) x -> DumpItem b #

(Show (BackendTableMeta bk), Show (BackendViewMeta bk), Show (BackendMaterializedViewMeta bk)) => GShow (SqlWrite bk a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlWrite

Methods

gshowsPrec :: Int -> SqlWrite bk a a0 -> ShowS #

(Show (BackendTableMeta bk), Show (BackendViewMeta bk), Show (BackendMaterializedViewMeta bk)) => Show (SqlWrite bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlWrite

Methods

showsPrec :: Int -> SqlWrite bk a b -> ShowS #

show :: SqlWrite bk a b -> String #

showList :: [SqlWrite bk a b] -> ShowS #

(Eq (BackendTableMeta bk), Eq (BackendViewMeta bk), Eq (BackendMaterializedViewMeta bk)) => Eq (SqlWrite bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlWrite

Methods

(==) :: SqlWrite bk a b -> SqlWrite bk a b -> Bool #

(/=) :: SqlWrite bk a b -> SqlWrite bk a b -> Bool #

data Cascade #

Constructors

Cascade 
Restrict 

Instances

Instances details
Show Cascade 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlWrite

Eq Cascade 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlWrite

Methods

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

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

createTableAsWithMeta :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => BackendTableMeta b -> Ref Table -> Query -> Sem r () #

createViewAsWithMeta :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => BackendViewMeta b -> Ref Table -> Query -> Sem r () #

insertIntoQuery :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Query -> Sem r () #

updateTable :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => UpdateQuery -> Sem r () #

copyTable :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Ref Table -> TableWriteStrategy -> Sem r () #

dropTable :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> MissingBehavior -> Cascade -> Sem r () #

dropMaterializedView :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> MissingBehavior -> Cascade -> Sem r () #

deleteFrom :: forall b (r :: EffectRow). Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> SExp -> Sem r () #

createTableAs :: forall b (r :: EffectRow). (Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r, Default (BackendTableMeta b)) => Ref Table -> Query -> Sem r () #

createViewAs :: forall b (r :: EffectRow). (Member (SqlWrite b :: (Type -> Type) -> Type -> Type) r, Default (BackendViewMeta b)) => Ref Table -> Query -> Sem r () #

newtype MetaArguments #

Constructors

MetaArguments 

newtype TargetName #

Constructors

TargetName (Ref Table) 

newtype HiddenArtifacts #

Constructors

HiddenArtifacts (Set (Ref Table)) 

Instances

Instances details
Default HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Monoid HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Semigroup HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

IsList HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Associated Types

type Item HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Show HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Eq HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

type Item HiddenArtifacts 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

newtype HiddenDependencies #

Constructors

HiddenDependencies (Set (Ref Table)) 

Instances

Instances details
Default HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Monoid HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Semigroup HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

IsList HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Associated Types

type Item HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Show HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Eq HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

type Item HiddenDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

newtype ExtraDependencies #

Constructors

ExtraDependencies (Set (Ref Table)) 

Instances

Instances details
Default ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Monoid ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Semigroup ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

IsList ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Associated Types

type Item ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Show ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

Eq ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

type Item ExtraDependencies 
Instance details

Defined in Napkin.Run.Effects.Languages.TableSpec

renameReferences :: forall (r :: EffectRow) a. Member (Reader QueryTransformer) r => (Ref Table -> Ref Table) -> Sem r a -> Sem r a #

Apply given table name renamer to every single reference occurrence everywhere.

If you want to target only certain tables, make sure the function you provide here does the filtering internally.

applyTransformer :: forall (r :: EffectRow) a. Member (Reader QueryTransformer) r => QueryTransformerUnit -> Sem r a -> Sem r a #

Comprehensively apply the given transformer around the given region.

hideDependencies :: forall a (r :: EffectRow). Member (Reader HiddenDependencies) r => Set (Ref Table) -> Sem r a -> Sem r a #

Add the given dependencies to the hide list around the given region.

Later during interpretation, this will cause the given dependencies to not be considered upstream dependencies within the enclosed region.

hideDependency :: forall a (r :: EffectRow). Member (Reader HiddenDependencies) r => Ref Table -> Sem r a -> Sem r a #

Add the given dependency to the hide list around the given region.

Later during interpretation, this will cause the given dependency to not be considered upstream dependency within the enclosed region.

hideArtifact :: forall a (r :: EffectRow). Member (Reader HiddenArtifacts) r => Ref Table -> Sem r a -> Sem r a #

Add the given artifact to the hide list around the given region.

Later during interpretation, this will cause the given artifact to not be reported to the tablespec within the enclosed region.

addDependencies :: forall (r :: EffectRow). Member (Output ExtraDependencies :: (Type -> Type) -> Type -> Type) r => Set (Ref Table) -> Sem r () #

Add the given references to list of dependencies for the underlying region.

Later during interpretation, this will cause the given dependencies to be forcefully considered upstream dependencies within the enclosed region even though they were not seen in the parsed SQL.

overrideTarget :: forall a (r :: EffectRow). Member (Reader TargetName) r => Ref Table -> Sem r a -> Sem r a #

insertQueryIntoTarget :: forall b (effs :: EffectRow). Members '[SqlWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => Query -> Sem effs () #

deleteFromTarget :: forall b (effs :: EffectRow). Members '[SqlWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => SExp -> Sem effs () #

updateTarget :: forall b (effs :: EffectRow). Members '[SqlWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => (Ref Relation -> U ()) -> Sem effs () #

data AnnotateRead (b :: k) (m :: k1) a #

Instances

Instances details
ToDumpItem (b :: k) (AnnotateRead b :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. AnnotateRead b (Sem r) x -> DumpItem b #

GShow (AnnotateRead bk a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

Methods

gshowsPrec :: Int -> AnnotateRead bk a a0 -> ShowS #

Show (AnnotateRead bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

Methods

showsPrec :: Int -> AnnotateRead bk a b -> ShowS #

show :: AnnotateRead bk a b -> String #

showList :: [AnnotateRead bk a b] -> ShowS #

Eq (AnnotateRead bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

Methods

(==) :: AnnotateRead bk a b -> AnnotateRead bk a b -> Bool #

(/=) :: AnnotateRead bk a b -> AnnotateRead bk a b -> Bool #

data TableAnnotations #

Instances

Instances details
Generic TableAnnotations 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

Associated Types

type Rep TableAnnotations 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

type Rep TableAnnotations = D1 ('MetaData "TableAnnotations" "Napkin.Run.Effects.Languages.AnnotateRead" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "TableAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "tableAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "columnsAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColumnsAnnotations)))
type Rep TableAnnotations 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateRead

type Rep TableAnnotations = D1 ('MetaData "TableAnnotations" "Napkin.Run.Effects.Languages.AnnotateRead" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "TableAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "tableAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "columnsAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColumnsAnnotations)))

getTargetAnnotations :: forall {k} (b :: k) (effs :: EffectRow). Members '[AnnotateRead b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => Sem effs TableAnnotations #

data AnnotateWrite (b :: k) (m :: k1) a #

Instances

Instances details
ToDumpItem (b :: k) (AnnotateWrite b :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. AnnotateWrite b (Sem r) x -> DumpItem b #

GShow (AnnotateWrite bk a :: Type -> Type) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateWrite

Methods

gshowsPrec :: Int -> AnnotateWrite bk a a0 -> ShowS #

Show (AnnotateWrite bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateWrite

Methods

showsPrec :: Int -> AnnotateWrite bk a b -> ShowS #

show :: AnnotateWrite bk a b -> String #

showList :: [AnnotateWrite bk a b] -> ShowS #

Eq (AnnotateWrite bk a b) 
Instance details

Defined in Napkin.Run.Effects.Languages.AnnotateWrite

Methods

(==) :: AnnotateWrite bk a b -> AnnotateWrite bk a b -> Bool #

(/=) :: AnnotateWrite bk a b -> AnnotateWrite bk a b -> Bool #

annotateTable :: forall {k} (b :: k) (r :: EffectRow). Member (AnnotateWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Text -> Sem r () #

annotateColumns :: forall {k} (b :: k) (r :: EffectRow). Member (AnnotateWrite b :: (Type -> Type) -> Type -> Type) r => Ref Table -> ColumnsAnnotations -> Sem r () #

annotateColumn :: forall {k} (b :: k) (effs :: EffectRow). Member (AnnotateWrite b :: (Type -> Type) -> Type -> Type) effs => Ref Table -> Ref SExp -> Text -> Sem effs () #

annotateTargetTable :: forall {k} (b :: k) (effs :: EffectRow). Members '[AnnotateWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => Text -> Sem effs () #

annotateTargetColumns :: forall {k} (b :: k) (effs :: EffectRow). Members '[AnnotateWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => ColumnsAnnotations -> Sem effs () #

annotateTargetColumn :: forall {k} (b :: k) (effs :: EffectRow). Members '[AnnotateWrite b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => Ref SExp -> Text -> Sem effs () #

data RecreateTable b (m :: k) a #

recreateTableAs :: forall b (r :: EffectRow). Member (RecreateTable b :: (Type -> Type) -> Type -> Type) r => BackendTableMeta b -> Ref Table -> NonEmpty Query -> Sem r () #

recreateViewAs :: forall b (r :: EffectRow). Member (RecreateTable b :: (Type -> Type) -> Type -> Type) r => BackendViewMeta b -> Ref Table -> Query -> Sem r () #

recreateTargetTable :: forall b (effs :: EffectRow). Members '[RecreateTable b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => BackendTableMeta b -> NonEmpty Query -> Sem effs () #

recreateTargetView :: forall b (effs :: EffectRow). Members '[RecreateTable b :: (Type -> Type) -> Type -> Type, Reader TargetName] effs => BackendViewMeta b -> Query -> Sem effs () #

askTextArgDefault :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Text -> Sem r Text #

askTextArg :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r Text #

askTextArgMb :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r (Maybe Text) #

askBoolArgDefault :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Bool -> Text -> Sem r Bool #

askBoolArg :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r Bool #

askBoolArgMb :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r (Maybe Bool) #

askNumArgDefault :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Scientific -> Text -> Sem r Scientific #

askNumArg :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r Scientific #

askNumArgMb :: forall (r :: EffectRow). Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r => Text -> Sem r (Maybe Scientific) #

askArg :: forall a (r :: EffectRow). (FromJSON a, Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r) => Text -> Sem r a #

askArgMb :: forall a (r :: EffectRow). (FromJSON a, Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type, Log :: (Type -> Type) -> Type -> Type] r) => Text -> Sem r (Maybe a) #

withTypedArg :: forall a b (r :: EffectRow). (Members '[Input MetaArguments :: (Type -> Type) -> Type -> Type, FatalError :: (Type -> Type) -> Type -> Type] r, FromJSON a, Typeable a) => (a -> Sem r b) -> Sem r b #

type SpecProgram b = SpecProgram' b () #

type HookProgram b = HookProgram' b () #

Hooks have different capabilities than specs

type HookProgram' b a = Sem (TableHookProgramEffects b) a #

Programs packaged up for use in Specs. Intended for use in providing introspectable CustomCreate actions in specs.