From dd81433d74579848e6853eb5a1500535c378c808 Mon Sep 17 00:00:00 2001 From: Jasper Van der Jeugt Date: Fri, 11 Feb 2011 13:30:55 +0100 Subject: Split Rules module, add documentation --- src/Hakyll/Core/CompiledItem.hs | 9 +++- src/Hakyll/Core/Compiler.hs | 2 +- src/Hakyll/Core/Rules.hs | 101 ++++++++++++++------------------------ src/Hakyll/Core/Rules/Internal.hs | 70 ++++++++++++++++++++++++++ src/Hakyll/Core/Run.hs | 2 +- 5 files changed, 117 insertions(+), 67 deletions(-) create mode 100644 src/Hakyll/Core/Rules/Internal.hs (limited to 'src') diff --git a/src/Hakyll/Core/CompiledItem.hs b/src/Hakyll/Core/CompiledItem.hs index fe6730b..5dd0efc 100644 --- a/src/Hakyll/Core/CompiledItem.hs +++ b/src/Hakyll/Core/CompiledItem.hs @@ -1,6 +1,11 @@ -- | A module containing a box datatype representing a compiled item. This --- item can be of any type, given that a few restrictions hold (e.g. we want --- a 'Typeable' instance to perform type-safe casts). +-- item can be of any type, given that a few restrictions hold: +-- +-- * we need a 'Typeable' instance to perform type-safe casts; +-- +-- * we need a 'Binary' instance so we can serialize these items to the cache; +-- +-- * we need a 'Writable' instance so the results can be saved. -- {-# LANGUAGE ExistentialQuantification #-} module Hakyll.Core.CompiledItem diff --git a/src/Hakyll/Core/Compiler.hs b/src/Hakyll/Core/Compiler.hs index 5249478..85b912c 100644 --- a/src/Hakyll/Core/Compiler.hs +++ b/src/Hakyll/Core/Compiler.hs @@ -38,7 +38,7 @@ import Hakyll.Core.Writable import Hakyll.Core.ResourceProvider import Hakyll.Core.Compiler.Internal import Hakyll.Core.Store -import Hakyll.Core.Rules +import Hakyll.Core.Rules.Internal import Hakyll.Core.Routes -- | Run a compiler, yielding the resulting target and it's dependencies. This diff --git a/src/Hakyll/Core/Rules.hs b/src/Hakyll/Core/Rules.hs index 28aac1f..fbdd533 100644 --- a/src/Hakyll/Core/Rules.hs +++ b/src/Hakyll/Core/Rules.hs @@ -1,13 +1,19 @@ --- | This module provides a monadic DSL in which the user can specify the --- different rules used to run the compilers +-- | This module provides a declarative DSL in which the user can specify the +-- different rules used to run the compilers. +-- +-- The convention is to just list all items in the 'RulesM' monad, routes and +-- compilation rules. +-- +-- A typical usage example would be: +-- +-- > main = hakyll $ do +-- > route "posts/*" (setExtension "html") +-- > compile "posts/*" someCompiler -- {-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-} module Hakyll.Core.Rules - ( CompileRule (..) - , RuleSet (..) - , RulesM + ( RulesM , Rules - , runRules , compile , create , route @@ -15,12 +21,12 @@ module Hakyll.Core.Rules , metaCompileWith ) where -import Control.Applicative (Applicative, (<$>)) -import Control.Monad.Writer (WriterT, execWriterT, tell) -import Control.Monad.Reader (ReaderT, runReaderT, ask) +import Control.Applicative ((<$>)) +import Control.Monad.Writer (tell) +import Control.Monad.Reader (ask) import Control.Arrow (second, (>>>), arr, (>>^)) -import Control.Monad.State (State, evalState, get, put) -import Data.Monoid (Monoid, mempty, mappend) +import Control.Monad.State (get, put) +import Data.Monoid (mempty) import Data.Typeable (Typeable) import Data.Binary (Binary) @@ -32,53 +38,7 @@ import Hakyll.Core.Compiler.Internal import Hakyll.Core.Routes import Hakyll.Core.CompiledItem import Hakyll.Core.Writable - --- | Output of a compiler rule --- --- * The compiler will produce a simple item. This is the most common case. --- --- * The compiler will produce more compilers. These new compilers need to be --- added to the runtime if possible, since other items might depend upon them. --- -data CompileRule = CompileRule CompiledItem - | MetaCompileRule [(Identifier, Compiler () CompileRule)] - --- | A collection of rules for the compilation process --- -data RuleSet = RuleSet - { rulesRoutes :: Routes - , rulesCompilers :: [(Identifier, Compiler () CompileRule)] - } - -instance Monoid RuleSet where - mempty = RuleSet mempty mempty - mappend (RuleSet r1 c1) (RuleSet r2 c2) = - RuleSet (mappend r1 r2) (mappend c1 c2) - --- | Rule state --- -data RuleState = RuleState - { rulesMetaCompilerIndex :: Int - } deriving (Show) - --- | The monad used to compose rules --- -newtype RulesM a = RulesM - { unRulesM :: ReaderT ResourceProvider (WriterT RuleSet (State RuleState)) a - } deriving (Monad, Functor, Applicative) - --- | Simplification of the RulesM type; usually, it will not return any --- result. --- -type Rules = RulesM () - --- | Run a Rules monad, resulting in a 'RuleSet' --- -runRules :: Rules -> ResourceProvider -> RuleSet -runRules rules provider = - evalState (execWriterT $ runReaderT (unRulesM rules) provider) state - where - state = RuleState {rulesMetaCompilerIndex = 0} +import Hakyll.Core.Rules.Internal -- | Add a route -- @@ -95,10 +55,11 @@ tellCompilers compilers = RulesM $ tell $ RuleSet mempty $ where boxCompiler = (>>> arr compiledItem >>> arr CompileRule) --- | Add a compilation rule +-- | Add a compilation rule to the rules. -- -- This instructs all resources matching the given pattern to be compiled using --- the given compiler +-- the given compiler. When no resources match the given pattern, nothing will +-- happen. In this case, you might want to have a look at 'create'. -- compile :: (Binary a, Typeable a, Writable a) => Pattern -> Compiler () a -> Rules @@ -108,18 +69,32 @@ compile pattern compiler = RulesM $ do -- | Add a compilation rule -- --- This sets a compiler for the given identifier +-- This sets a compiler for the given identifier. No resource is needed, since +-- we are creating the item from scratch. -- create :: (Binary a, Typeable a, Writable a) => Identifier -> Compiler () a -> Rules create identifier compiler = tellCompilers [(identifier, compiler)] --- | Add a route +-- | Add a route. +-- +-- This adds a route for all items matching the given pattern. -- route :: Pattern -> Routes -> Rules route pattern route' = tellRoute $ ifMatch pattern route' --- | Add a compiler that produces other compilers over time +-- | Apart from regular compilers, one is also able to specify metacompilers. +-- Metacompilers are a special class of compilers: they are compilers which +-- produce other compilers. +-- +-- And indeed, we can see that the first argument to 'metaCompile' is a +-- 'Compiler' which produces a list of ('Identifier', 'Compiler') pairs. The +-- idea is simple: 'metaCompile' produces a list of compilers, and the +-- corresponding identifiers. +-- +-- For simple hakyll systems, it is no need for this construction. More +-- formally, it is only needed when the content of one or more items determines +-- which items must be rendered. -- metaCompile :: (Binary a, Typeable a, Writable a) => Compiler () [(Identifier, Compiler () a)] diff --git a/src/Hakyll/Core/Rules/Internal.hs b/src/Hakyll/Core/Rules/Internal.hs new file mode 100644 index 0000000..bedc67a --- /dev/null +++ b/src/Hakyll/Core/Rules/Internal.hs @@ -0,0 +1,70 @@ +-- | Internal rules module for types which are not exposed to the user +-- +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Hakyll.Core.Rules.Internal + ( CompileRule (..) + , RuleSet (..) + , RuleState (..) + , RulesM (..) + , Rules + , runRules + ) where + +import Control.Applicative (Applicative) +import Control.Monad.Writer (WriterT, execWriterT) +import Control.Monad.Reader (ReaderT, runReaderT) +import Control.Monad.State (State, evalState) +import Data.Monoid (Monoid, mempty, mappend) + +import Hakyll.Core.ResourceProvider +import Hakyll.Core.Identifier +import Hakyll.Core.Compiler.Internal +import Hakyll.Core.Routes +import Hakyll.Core.CompiledItem + +-- | Output of a compiler rule +-- +-- * The compiler will produce a simple item. This is the most common case. +-- +-- * The compiler will produce more compilers. These new compilers need to be +-- added to the runtime if possible, since other items might depend upon them. +-- +data CompileRule = CompileRule CompiledItem + | MetaCompileRule [(Identifier, Compiler () CompileRule)] + +-- | A collection of rules for the compilation process +-- +data RuleSet = RuleSet + { rulesRoutes :: Routes + , rulesCompilers :: [(Identifier, Compiler () CompileRule)] + } + +instance Monoid RuleSet where + mempty = RuleSet mempty mempty + mappend (RuleSet r1 c1) (RuleSet r2 c2) = + RuleSet (mappend r1 r2) (mappend c1 c2) + +-- | Rule state +-- +data RuleState = RuleState + { rulesMetaCompilerIndex :: Int + } deriving (Show) + +-- | The monad used to compose rules +-- +newtype RulesM a = RulesM + { unRulesM :: ReaderT ResourceProvider (WriterT RuleSet (State RuleState)) a + } deriving (Monad, Functor, Applicative) + +-- | Simplification of the RulesM type; usually, it will not return any +-- result. +-- +type Rules = RulesM () + +-- | Run a Rules monad, resulting in a 'RuleSet' +-- +runRules :: Rules -> ResourceProvider -> RuleSet +runRules rules provider = + evalState (execWriterT $ runReaderT (unRulesM rules) provider) state + where + state = RuleState {rulesMetaCompilerIndex = 0} diff --git a/src/Hakyll/Core/Run.hs b/src/Hakyll/Core/Run.hs index de4114c..7e6851f 100644 --- a/src/Hakyll/Core/Run.hs +++ b/src/Hakyll/Core/Run.hs @@ -25,7 +25,7 @@ import Hakyll.Core.Compiler import Hakyll.Core.Compiler.Internal import Hakyll.Core.ResourceProvider import Hakyll.Core.ResourceProvider.FileResourceProvider -import Hakyll.Core.Rules +import Hakyll.Core.Rules.Internal import Hakyll.Core.DirectedGraph import Hakyll.Core.DirectedGraph.DependencySolver import Hakyll.Core.Writable -- cgit v1.2.3