Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Writer w f a where
- type Rules f = GenRules f f
- type GenRules f g = forall a. f a -> Task g a
- newtype Task f a = Task {}
- class Monad m => MonadFetch f m | m -> f where
- fetch :: f a -> m a
- newtype Cyclic f = Cyclic (Some f)
- data MemoEntry a
- data TaskKind
- type ReverseDependencies f = HashMap (Some f) (HashSet (Some f))
- writer :: forall f w g. (forall a. f a -> w -> Task g ()) -> GenRules (Writer w f) g -> GenRules f g
- transFetch :: (forall b. f b -> Task f' b) -> Task f a -> Task f' a
- runTask :: Rules f -> Task f a -> IO a
- track :: forall f g a. (GEq f, Hashable (Some f)) => (forall a'. f a' -> a' -> g a') -> Task f a -> Task f (a, DHashMap f g)
- trackM :: forall f g a. (GEq f, Hashable (Some f)) => (forall a'. f a' -> a' -> Task f (g a')) -> Task f a -> Task f (a, DHashMap f g)
- memoise :: forall f g. (GEq f, Hashable (Some f)) => IORef (DHashMap f MVar) -> GenRules f g -> GenRules f g
- memoiseWithCycleDetection :: forall f g. (Typeable f, GShow f, GEq f, Hashable (Some f)) => IORef (DHashMap f MemoEntry) -> IORef (HashMap ThreadId ThreadId) -> GenRules f g -> GenRules f g
- verifyTraces :: forall f dep. (Hashable (Some f), GEq f, Has' Eq f dep, Typeable f, GShow f) => IORef (Traces f dep) -> (forall a. f a -> a -> Task f (dep a)) -> GenRules (Writer TaskKind f) f -> Rules f
- traceFetch :: (forall a. f a -> Task g ()) -> (forall a. f a -> a -> Task g ()) -> GenRules f g -> GenRules f g
- trackReverseDependencies :: (GEq f, Hashable (Some f)) => IORef (ReverseDependencies f) -> Rules f -> Rules f
- reachableReverseDependencies :: (GEq f, Hashable (Some f)) => f a -> ReverseDependencies f -> (DHashMap f (Const ()), ReverseDependencies f)
- type Traces f dep = DHashMap f (ValueDeps f dep)
Documentation
data Writer w f a where Source #
A query that returns a w
alongside the ordinary a
.
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.
class Monad m => MonadFetch f m | m -> f where Source #
Monads that can make f
queries by fetch
ing them.
Nothing
default fetch :: (MonadTrans t, MonadFetch f m1, m ~ t m1) => f a -> m a Source #
Instances
MonadFetch f (Task f) Source # | |
MonadFetch f m => MonadFetch f (MaybeT m) Source # | |
MonadFetch f m => MonadFetch f (ExceptT e m) Source # | |
MonadFetch f m => MonadFetch f (IdentityT m) Source # | |
MonadFetch f m => MonadFetch f (ReaderT r m) Source # | |
MonadFetch f m => MonadFetch f (StateT s m) Source # | |
MonadFetch f m => MonadFetch f (StateT s 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 (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 # | |
Instances
(GShow f, Typeable f) => Exception (Cyclic f) Source # | |
Defined in Rock.Core toException :: Cyclic f -> SomeException # fromException :: SomeException -> Maybe (Cyclic f) # displayException :: Cyclic f -> String # | |
GShow f => Show (Cyclic 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
.
transFetch :: (forall b. f b -> Task f' b) -> Task f a -> Task f' a Source #
Transform the type of queries that a Task
performs.
track :: forall f g a. (GEq f, Hashable (Some f)) => (forall a'. f a' -> a' -> g a') -> Task f a -> Task f (a, DHashMap f g) Source #
trackM :: forall f g a. (GEq f, Hashable (Some f)) => (forall a'. f a' -> a' -> Task f (g a')) -> Task f a -> Task f (a, DHashMap f g) Source #
memoise :: forall f g. (GEq f, Hashable (Some f)) => IORef (DHashMap f MVar) -> GenRules f g -> GenRules f g Source #
memoiseWithCycleDetection :: forall f g. (Typeable f, GShow f, GEq f, Hashable (Some f)) => IORef (DHashMap f MemoEntry) -> IORef (HashMap ThreadId ThreadId) -> GenRules f g -> GenRules f g Source #
verifyTraces :: forall f dep. (Hashable (Some f), GEq f, Has' Eq f dep, Typeable f, GShow f) => IORef (Traces f dep) -> (forall a. f a -> a -> Task f (dep a)) -> GenRules (Writer TaskKind f) f -> Rules f Source #
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
.
trackReverseDependencies :: (GEq f, Hashable (Some f)) => IORef (ReverseDependencies f) -> Rules f -> Rules f Source #
Write reverse dependencies to the 'IORef.
reachableReverseDependencies :: (GEq f, Hashable (Some f)) => f a -> ReverseDependencies f -> (DHashMap f (Const ()), ReverseDependencies f) Source #
returns all keys reachable, by
reverse dependency, from reachableReverseDependencies
keykey
from the input DHashMap
. It also returns the
reverse dependency map with those same keys removed.