Safe Haskell | None |
---|---|
Language | GHC2024 |
Documentation
newtype TopSortPrio #
Instances
Show TopSortPrio # | |
Defined in Napkin.Cli.Web.Effects showsPrec :: Int -> TopSortPrio -> ShowS # show :: TopSortPrio -> String # showList :: [TopSortPrio] -> ShowS # | |
Eq TopSortPrio # | |
Defined in Napkin.Cli.Web.Effects (==) :: TopSortPrio -> TopSortPrio -> Bool # (/=) :: TopSortPrio -> TopSortPrio -> Bool # | |
Ord TopSortPrio # | |
Defined in Napkin.Cli.Web.Effects compare :: TopSortPrio -> TopSortPrio -> Ordering # (<) :: TopSortPrio -> TopSortPrio -> Bool # (<=) :: TopSortPrio -> TopSortPrio -> Bool # (>) :: TopSortPrio -> TopSortPrio -> Bool # (>=) :: TopSortPrio -> TopSortPrio -> Bool # max :: TopSortPrio -> TopSortPrio -> TopSortPrio # min :: TopSortPrio -> TopSortPrio -> TopSortPrio # |
data DAG b (a :: Type -> Type) c where #
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
type DispatchOf (DAG b) # | |
Defined in Napkin.Cli.Web.Effects |
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) #
data TaskStates (b :: k) #
TaskStates | |
|
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) #
initTaskStates :: forall b m. MonadUnliftIO m => TasksDAG Full 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 #
UITask | |
|
Instances
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)) #
getTaskState :: forall {k} b (f :: k) (es :: [Effect]). DAG b :> es => (FullDAG b -> TasksDAG f b) -> TaskId -> Eff es (Maybe (UITask b)) #
data Execution (a :: Type -> Type) b where #
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
type DispatchOf Execution # | |
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 #
initExecutionVar :: MonadIO m => m (TMVar UIExecutionControl) #
data Time (a :: Type -> Type) b where #
GetCurrentTime :: forall (a :: Type -> Type). Time a UTCTime |
Instances
type DispatchOf Time # | |
Defined in Napkin.Cli.Web.Effects |