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

Safe HaskellNone
LanguageHaskell2010

Rock.Core

Contents

Synopsis

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.

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
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 #

data Result f a Source #

The result of a Task, which is either done or wanting to make one or more f queries.

Constructors

Done a 
Blocked !(BlockedTask f a) 
Instances
Monad (Result f) Source # 
Instance details

Defined in Rock.Core

Methods

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

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

return :: a -> Result f a #

fail :: String -> Result f a #

Functor (Result f) Source # 
Instance details

Defined in Rock.Core

Methods

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

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

Applicative (Result f) Source # 
Instance details

Defined in Rock.Core

Methods

pure :: a -> Result f a #

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

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

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

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

data BlockedTask f a where Source #

Constructors

BlockedTask :: Block f a -> (a -> Task f b) -> BlockedTask f b 
Instances
Functor (BlockedTask f) Source # 
Instance details

Defined in Rock.Core

Methods

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

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

data Block f a where Source #

Constructors

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 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 m => MonadFetch f (Sequential m) Source # 
Instance details

Defined in Rock.Core

Methods

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

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 #

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 #

transFetchBlock :: (forall b. f b -> Task f' b) -> Block 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 :: Sequential (Task f) a, this means that fetches within m are done sequentially.

Constructors

Sequential 

Fields

Instances
MonadFetch f m => MonadFetch f (Sequential m) Source # 
Instance details

Defined in Rock.Core

Methods

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

Monad m => Monad (Sequential m) Source # 
Instance details

Defined in Rock.Core

Methods

(>>=) :: Sequential m a -> (a -> Sequential m b) -> Sequential m b #

(>>) :: Sequential m a -> Sequential m b -> Sequential m b #

return :: a -> Sequential m a #

fail :: String -> Sequential m a #

Functor m => Functor (Sequential m) Source # 
Instance details

Defined in Rock.Core

Methods

fmap :: (a -> b) -> Sequential m a -> Sequential m b #

(<$) :: a -> Sequential m b -> Sequential m a #

Monad m => Applicative (Sequential m) Source #

Defined in terms of return and '(>>=)'.

Instance details

Defined in Rock.Core

Methods

pure :: a -> Sequential m a #

(<*>) :: Sequential m (a -> b) -> Sequential m a -> Sequential m b #

liftA2 :: (a -> b -> c) -> Sequential m a -> Sequential m b -> Sequential m c #

(*>) :: Sequential m a -> Sequential m b -> Sequential m b #

(<*) :: Sequential m a -> Sequential m b -> Sequential m a #

MonadIO m => MonadIO (Sequential m) Source # 
Instance details

Defined in Rock.Core

Methods

liftIO :: IO a -> Sequential m a #

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.

runBlock :: Strategy -> Rules f -> Block f a -> IO a Source #

Task combinators

track :: forall f a. GCompare f => Task f a -> Task f (a, DMap f Identity) Source #

Track the query dependencies of a Task in a DMap

memoise :: forall f g. GCompare f => MVar (DMap f MVar) -> GenRules f g -> GenRules f g Source #

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

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

verifyTraces :: (GCompare f, HashTag f) => MVar (Traces f) -> 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. The DMap _can_ be reused if there are changes to Input queries.

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 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
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 #

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) #

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.