summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Rules
diff options
context:
space:
mode:
authorJasper Van der Jeugt <jaspervdj@gmail.com>2011-02-11 13:30:55 +0100
committerJasper Van der Jeugt <jaspervdj@gmail.com>2011-02-11 13:30:55 +0100
commitdd81433d74579848e6853eb5a1500535c378c808 (patch)
treecb0c4c2db47b6ac7a5456be21fa9550b41b0b6ea /src/Hakyll/Core/Rules
parent2dfe7f6a674657d006d71eac25931bfd629b78a2 (diff)
downloadhakyll-dd81433d74579848e6853eb5a1500535c378c808.tar.gz
Split Rules module, add documentation
Diffstat (limited to 'src/Hakyll/Core/Rules')
-rw-r--r--src/Hakyll/Core/Rules/Internal.hs70
1 files changed, 70 insertions, 0 deletions
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}