Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Rules f = GenRules f f
- type GenRules f g = forall a. f a -> Task g a
- newtype Task f a = Task {}
- data Result f a
- = Done a
- | Blocked !(BlockedTask f a)
- data BlockedTask f a where
- BlockedTask :: Block f a -> (a -> Task f b) -> BlockedTask f b
- data Block f a where
- Fetch :: f a -> Block f a
- Ap :: !(BlockedTask f (a -> b)) -> !(BlockedTask f a) -> Block f b
- class Monad m => MonadFetch f m | m -> f where
- fetch :: f a -> m a
- transFetch :: (forall b. f b -> Task f' b) -> Task f a -> Task f' a
- transFetchBlockedTask :: (forall b. f b -> Task f' b) -> BlockedTask f a -> Task f' a
- transFetchBlock :: (forall b. f b -> Task f' b) -> Block f a -> Task f' a
- type Strategy = forall a b. IO (a -> b) -> IO a -> IO b
- sequentially :: Strategy
- inParallel :: Strategy
- newtype Sequential m a = Sequential {
- runSequential :: m a
- runTask :: Strategy -> Rules f -> Task f a -> IO a
- runBlockedTask :: Strategy -> Rules f -> BlockedTask f a -> IO a
- runBlock :: Strategy -> Rules f -> Block f a -> IO a
- track :: forall f a. GCompare f => Task f a -> Task f (a, DMap f Identity)
- memoise :: forall f g. GCompare f => MVar (DMap f MVar) -> GenRules f g -> GenRules f g
- verifyTraces :: (GCompare f, HashTag f) => MVar (Traces f) -> GenRules (Writer TaskKind f) f -> Rules f
- data TaskKind
- data Writer w f a where
- writer :: forall f w g. (forall a. f a -> w -> Task g ()) -> GenRules (Writer w f) g -> GenRules f g
- traceFetch :: (forall a. f a -> Task g ()) -> (forall a. f a -> a -> Task g ()) -> GenRules f g -> GenRules f g
Types
type Rules f = GenRules f f Source #
A function which, given an f
query, returns a Task
allowed to make f
queries to compute its result.
type GenRules f g = forall a. f a -> Task g a Source #
A function which, given an f
query, returns a Task
allowed to make g
queries to compute its result.
An IO
action that is allowed to make f
queries using the fetch
method from its MonadFetch
instance.
The result of a Task
, which is either done or wanting to make one or
more f
queries.
Done a | |
Blocked !(BlockedTask f a) |
data BlockedTask f a where Source #
BlockedTask :: Block f a -> (a -> Task f b) -> BlockedTask f b |
Instances
Functor (BlockedTask f) Source # | |
Defined in Rock.Core fmap :: (a -> b) -> BlockedTask f a -> BlockedTask f b # (<$) :: a -> BlockedTask f b -> BlockedTask f a # |
Fetch :: f a -> Block f a | |
Ap :: !(BlockedTask f (a -> b)) -> !(BlockedTask f a) -> Block f b |
Fetch class
class Monad m => MonadFetch f m | m -> f where Source #
Monads that can make f
queries by fetch
ing them.
Nothing
fetch :: (MonadTrans t, MonadFetch f m1, m ~ t m1) => f a -> m a Source #
Instances
MonadFetch f m => MonadFetch f (Sequential m) Source # | |
Defined in Rock.Core fetch :: f a -> Sequential m a Source # | |
MonadFetch f (Task f) Source # | |
MonadFetch f m => MonadFetch f (MaybeT m) Source # | |
(Monoid w, MonadFetch f m) => MonadFetch f (WriterT w m) Source # | |
(Monoid w, MonadFetch f m) => MonadFetch f (WriterT w m) Source # | |
MonadFetch f m => MonadFetch f (StateT s m) Source # | |
MonadFetch f m => MonadFetch f (StateT s m) Source # | |
MonadFetch f m => MonadFetch f (IdentityT m) Source # | |
MonadFetch f m => MonadFetch f (ExceptT e m) Source # | |
MonadFetch f m => MonadFetch f (ReaderT r m) Source # | |
MonadFetch f m => MonadFetch f (ContT r m) Source # | |
(MonadFetch f m, Monoid w) => MonadFetch f (RWST r w s m) Source # | |
(MonadFetch f m, Monoid w) => MonadFetch f (RWST r w s m) Source # | |
Transformations
transFetch :: (forall b. f b -> Task f' b) -> Task f a -> Task f' a Source #
Transform the type of queries that a Task
performs.
transFetchBlockedTask :: (forall b. f b -> Task f' b) -> BlockedTask f a -> Task f' a Source #
Strategies
type Strategy = forall a b. IO (a -> b) -> IO a -> IO b Source #
A Strategy
specifies how two queries are performed in an Applicative
context.
sequentially :: Strategy Source #
Runs the two queries in sequence.
inParallel :: Strategy Source #
Runs the two queries in parallel.
newtype Sequential m a Source #
Uses the underlying instances, except for the Applicative instance which
is defined in terms of return
and '(>>=)'.
When used with Task
, i.e. if you construct m ::
, this means that fetches within Sequential
(Task
f)
am
are done sequentially.
Sequential | |
|
Instances
Running tasks
runTask :: Strategy -> Rules f -> Task f a -> IO a Source #
Perform a Task
, fetching dependency queries from the given Rules
function and using the given Strategy
for fetches in an Applicative
context.
runBlockedTask :: Strategy -> Rules f -> BlockedTask f a -> IO a Source #
Task combinators
verifyTraces :: (GCompare f, HashTag f) => MVar (Traces f) -> GenRules (Writer TaskKind f) f -> Rules f Source #
writer :: forall f w g. (forall a. f a -> w -> Task g ()) -> GenRules (Writer w f) g -> GenRules f g Source #
runs writer
write ruleswrite w
each time a w
is returned from a
rule in rules
.
traceFetch :: (forall a. f a -> Task g ()) -> (forall a. f a -> a -> Task g ()) -> GenRules f g -> GenRules f g Source #
runs traceFetch
before after rulesbefore q
before a query is
performed from rules
, and after q result
every time a query returns with
result result
.