napkin-cli-2.0.0
Safe HaskellNone
LanguageGHC2024

Napkin.Cli.Web.Effects

Documentation

type Plan b = TasksDAG Exec b #

type FullDAG b = TasksDAG Full b #

newtype Warns #

Constructors

Warns [Text] 

data DAG b (a :: Type -> Type) c where #

Constructors

GetDAG :: forall {k} b (f :: k) (a :: Type -> Type). (FullDAG b -> TasksDAG f b) -> DAG b a (TasksDAG f b) 
GetTaskStates :: forall {k} b (f :: k) (a :: Type -> Type). (FullDAG b -> TasksDAG f b) -> DAG b a (Map TaskId (UITask b)) 
IsFinished :: forall b (a :: Type -> Type). DAG b a Bool 
SetTableSelectors :: forall b (a :: Type -> Type). [RunTableSelector] -> DAG b a Warns 
GetEstimatedTotalRuntime :: forall b (a :: Type -> Type). DAG b a Estimate 
GetTableSelectors :: forall b (a :: Type -> Type). DAG b a [RunTableSelector] 

Instances

Instances details
type DispatchOf (DAG b) # 
Instance details

Defined in Napkin.Cli.Web.Effects

type DispatchOf (DAG b) = 'Dynamic

runDAGIO :: forall b (es :: [Effect]) a. (Concurrent :> es, Renamer :> es, Reader (Map TaskId NominalDiffTime) :> es, Reader UTCTime :> es, IOE :> es, Reader (FullDAG b) :> es) => Maybe ([RunTableSelector] -> TasksDAG Full b -> IO (TasksDAG Full b, [Text])) -> TaskStates b -> Eff (DAG b ': es) a -> Eff es a #

mergeTaskStates :: forall {k} (rep :: k) b. TasksDAG rep b -> Map TaskId NominalDiffTime -> Map TaskId (TaskStateInfo b) -> Map TaskId (UITask b) #

getDagImpl :: forall {k} b (es :: [Effect]) (f :: k). (Reader (FullDAG b) :> es, Concurrent :> es) => TVar (Map TaskId ExecutionReason) -> (FullDAG b -> TasksDAG f b) -> Eff es (TasksDAG f b) #

mkTaskStates :: forall {k} (b :: k) m. MonadUnliftIO m => DAGRunState b -> Estimate -> [RunTableSelector] -> m (TaskStates b) #

accumTaskStates :: forall {k} (b :: k) m. MonadUnliftIO m => RuntimeEventQueueDAG b -> Estimate -> [RunTableSelector] -> m (TaskStates b) #

updateTableSelectors :: forall b (es :: [Effect]). DAG b :> es => [RunTableSelector] -> Eff es Warns #

data UITask b #

Instances

Instances details
Generic (UITask b) # 
Instance details

Defined in Napkin.Cli.Web.Effects

Associated Types

type Rep (UITask b) 
Instance details

Defined in Napkin.Cli.Web.Effects

type Rep (UITask b) = D1 ('MetaData "UITask" "Napkin.Cli.Web.Effects" "napkin-cli-2.0.0-4ha97GXrcwU2qMy5j7dc75" 'False) (C1 ('MetaCons "UITask" 'PrefixI 'True) (S1 ('MetaSel ('Just "task") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Task (Executable b))) :*: (S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TaskStateInfo b))) :*: S1 ('MetaSel ('Just "estimate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NominalDiffTime)))))

Methods

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

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

type Rep (UITask b) # 
Instance details

Defined in Napkin.Cli.Web.Effects

type Rep (UITask b) = D1 ('MetaData "UITask" "Napkin.Cli.Web.Effects" "napkin-cli-2.0.0-4ha97GXrcwU2qMy5j7dc75" 'False) (C1 ('MetaCons "UITask" 'PrefixI 'True) (S1 ('MetaSel ('Just "task") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Task (Executable b))) :*: (S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TaskStateInfo b))) :*: S1 ('MetaSel ('Just "estimate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NominalDiffTime)))))

getDAG :: forall {k} b (f :: k) (es :: [Effect]). DAG b :> es => (FullDAG b -> TasksDAG f b) -> Eff es (TasksDAG f b) #

getTableSelectors :: forall b (es :: [Effect]). DAG b :> es => Eff es [RunTableSelector] #

getTaskStates :: forall {k} b (f :: k) (es :: [Effect]). DAG b :> es => (FullDAG b -> TasksDAG f b) -> Eff es (Map TaskId (UITask b)) #

getEstimatedTotalRuntime :: forall b (es :: [Effect]). DAG b :> es => Eff es Estimate #

getTaskState :: forall {k} b (f :: k) (es :: [Effect]). DAG b :> es => (FullDAG b -> TasksDAG f b) -> TaskId -> Eff es (Maybe (UITask b)) #

isFinished :: forall b (es :: [Effect]). DAG b :> es => Eff es Bool #

data Execution (a :: Type -> Type) b where #

Constructors

Pause :: forall (a :: Type -> Type). Execution a () 
IsPaused :: forall (a :: Type -> Type). Execution a Bool 
Quit :: forall (a :: Type -> Type). Execution a () 
IsQuitting :: forall (a :: Type -> Type). Execution a Bool 

Instances

Instances details
type DispatchOf Execution # 
Instance details

Defined in Napkin.Cli.Web.Effects

runExecution :: forall (es :: [Effect]) a. Concurrent :> es => TMVar UIExecutionControl -> Eff (Execution ': es) a -> Eff es a #

dummyExecution :: forall (es :: [Effect]) a. Concurrent :> es => Eff (Execution ': es) a -> Eff es a #

pause :: forall (es :: [Effect]). Execution :> es => Eff es () #

isPaused :: forall (es :: [Effect]). Execution :> es => Eff es Bool #

quit :: forall (es :: [Effect]). Execution :> es => Eff es () #

isQuitting :: forall (es :: [Effect]). Execution :> es => Eff es Bool #

data Time (a :: Type -> Type) b where #

Constructors

GetCurrentTime :: forall (a :: Type -> Type). Time a UTCTime 

Instances

Instances details
type DispatchOf Time # 
Instance details

Defined in Napkin.Cli.Web.Effects

runTime :: forall (es :: [Effect]) a. IOE :> es => Eff (Time ': es) a -> Eff es a #

getCurrentTime :: forall (es :: [Effect]). Time :> es => Eff es UTCTime #