Safe Haskell | None |
---|---|
Language | Haskell2010 |
Achille.Internal
Description
Defines recipes, how they compose and evaluate.
Synopsis
- type Cache = ByteString
- emptyCache :: Cache
- toCache :: Binary a => a -> Cache
- fromCache :: Binary a => Cache -> Maybe a
- fromContext :: Binary a => Context b -> (Maybe a, Context b)
- data MustRun
- data Context a = Context {
- inputDir :: FilePath
- outputDir :: FilePath
- currentDir :: FilePath
- timestamp :: UTCTime
- forceFiles :: [Pattern]
- mustRun :: MustRun
- cache :: Cache
- inputValue :: a
- newtype Recipe m a b = Recipe (Context a -> m (b, Cache))
- type Task m = Recipe m ()
- runRecipe :: Recipe m a b -> Context a -> m (b, Cache)
- nonCached :: Functor m => (Context a -> m b) -> Recipe m a b
Documentation
type Cache = ByteString Source #
A cache is a lazy bytestring.
emptyCache :: Cache Source #
The empty cache.
fromContext :: Binary a => Context b -> (Maybe a, Context b) Source #
Try to load a value from the cache, while respecting the rule for running the recipe. That is, if the rule must run, nothing will be returned. We also lower the run rule in the returned context, if possible.
The types are not explicit enough, should rewrite.
Local rules for running a recipe
Constructors
MustRunOne | The current recipe, and only this one, must run |
MustRunAll | All subsequent recipes must run |
NoMust | No obligation, the current recipe will be run as normal |
Context in which a recipe is being executed.
Constructors
Context | |
Fields
|
Description of a computation producing a value b given some input a.
Instances
Monad m => Monad (Recipe m a) Source # | |
Functor m => Functor (Recipe m a) Source # | |
MonadFail m => MonadFail (Recipe m a) Source # | |
Defined in Achille.Internal | |
Monad m => Applicative (Recipe m a) Source # | |
Defined in Achille.Internal | |
MonadIO m => MonadIO (Recipe m a) Source # | |
Defined in Achille.Internal | |
(Monad m, Semigroup b) => Semigroup (Recipe m a b) Source # | |
(Monad m, Monoid b) => Monoid (Recipe m a b) Source # | |