rock-0.3.0.0: A build system for incremental, parallel, and demand-driven computations

Safe HaskellNone
LanguageHaskell2010

Rock

Synopsis

Documentation

data Writer w f a where Source #

A query that returns a w alongside the ordinary a.

Constructors

Writer :: f a -> Writer w f (a, w) 
Instances
GEq f => GEq (Writer w f :: Type -> Type) Source # 
Instance details

Defined in Rock.Core

Methods

geq :: Writer w f a -> Writer w f b -> Maybe (a :~: b) #

GCompare f => GCompare (Writer w f :: Type -> Type) Source # 
Instance details

Defined in Rock.Core

Methods

gcompare :: Writer w f a -> Writer w f b -> GOrdering a b #

data TaskKind Source #

Constructors

Input

Used for tasks whose results can change independently of their fetched dependencies, i.e. inputs.

NonInput

Used for task whose results only depend on fetched dependencies.

data MemoEntry a Source #

Constructors

Started !ThreadId !(MVar (Maybe a)) 
Done !a 

newtype Cyclic f Source #

Constructors

Cyclic (Some f) 
Instances
GShow f => Show (Cyclic f) Source # 
Instance details

Defined in Rock.Core

Methods

showsPrec :: Int -> Cyclic f -> ShowS #

show :: Cyclic f -> String #

showList :: [Cyclic f] -> ShowS #

(GShow f, Typeable f) => Exception (Cyclic f) Source # 
Instance details

Defined in Rock.Core

class Monad m => MonadFetch f m | m -> f where Source #

Monads that can make f queries by fetching them.

Minimal complete definition

Nothing

Methods

fetch :: f a -> m a Source #

fetch :: (MonadTrans t, MonadFetch f m1, m ~ t m1) => f a -> m a Source #

Instances
MonadFetch f (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> Task f a Source #

MonadFetch f m => MonadFetch f (MaybeT m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> MaybeT m a Source #

(Monoid w, MonadFetch f m) => MonadFetch f (WriterT w m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> WriterT w m a Source #

(Monoid w, MonadFetch f m) => MonadFetch f (WriterT w m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> WriterT w m a Source #

MonadFetch f m => MonadFetch f (StateT s m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> StateT s m a Source #

MonadFetch f m => MonadFetch f (StateT s m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> StateT s m a Source #

MonadFetch f m => MonadFetch f (IdentityT m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> IdentityT m a Source #

MonadFetch f m => MonadFetch f (ExceptT e m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> ExceptT e m a Source #

MonadFetch f m => MonadFetch f (ReaderT r m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> ReaderT r m a Source #

MonadFetch f m => MonadFetch f (ContT r m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> ContT r m a Source #

(MonadFetch f m, Monoid w) => MonadFetch f (RWST r w s m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> RWST r w s m a Source #

(MonadFetch f m, Monoid w) => MonadFetch f (RWST r w s m) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> RWST r w s m a Source #

newtype Task f a Source #

An IO action that is allowed to make f queries using the fetch method from its MonadFetch instance.

Constructors

Task 

Fields

Instances
MonadBase IO (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

liftBase :: IO α -> Task f α #

MonadBaseControl IO (Task f) Source # 
Instance details

Defined in Rock.Core

Associated Types

type StM (Task f) a :: Type #

Methods

liftBaseWith :: (RunInBase (Task f) IO -> IO a) -> Task f a #

restoreM :: StM (Task f) a -> Task f a #

MonadFetch f (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

fetch :: f a -> Task f a Source #

Monad (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

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

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

return :: a -> Task f a #

fail :: String -> Task f a #

Functor (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

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

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

Applicative (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

pure :: a -> Task f a #

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

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

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

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

MonadIO (Task f) Source # 
Instance details

Defined in Rock.Core

Methods

liftIO :: IO a -> Task f a #

type StM (Task f) a Source # 
Instance details

Defined in Rock.Core

type StM (Task f) a = StM (ReaderT (Fetch f) IO) a

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.

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.

transFetch :: (forall b. f b -> Task f' b) -> Task f a -> Task f' a Source #

Transform the type of queries that a Task performs.

runTask :: Rules f -> Task f a -> IO a Source #

Perform a Task, fetching dependency queries from the given Rules function.

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 #

Track the query dependencies of a Task in a DHashMap.

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 #

Track the query dependencies of a Task in a DHashMap. Monadic version.

memoise :: forall f g. (GEq f, Hashable (Some f)) => IORef (DHashMap f MVar) -> GenRules f g -> GenRules f g Source #

Remember what f queries have already been performed and their results in a DHashMap, and reuse them if a query is performed again a second time.

The DHashMap should typically not be reused if there has been some change that might make a query return a different result.

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 #

Like memoise, but throw Cyclic f if a query depends on itself, directly or indirectly.

The HashMap represents dependencies between threads and should not be reused between invocations.

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 #

Remember the results of previous f queries and what their dependencies were then.

If all dependencies of a NonInput query are the same, reuse the old result. Input queries are not reused.

writer :: forall f w g. (forall a. f a -> w -> Task g ()) -> GenRules (Writer w f) g -> GenRules f g Source #

writer write rules runs write 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 #

traceFetch before after rules runs before 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 #

reachableReverseDependencies key returns all keys reachable, by reverse dependency, from key from the input DHashMap. It also returns the reverse dependency map with those same keys removed.

type Traces f dep = DHashMap f (ValueDeps f dep) Source #