hakyll/src/Hakyll/Core/Rules.hs

97 lines
2.6 KiB
Haskell
Raw Normal View History

2010-12-25 18:37:21 +00:00
-- | This module provides a monadic DSL in which the user can specify the
-- different rules used to run the compilers
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Rules
( RuleSet (..)
, RulesM
, Rules
, runRules
, compile
, create
, route
) where
import Control.Applicative (Applicative, (<$>))
import Control.Monad.Writer
import Control.Monad.Reader
2010-12-29 21:59:38 +00:00
import Control.Arrow (second, (>>>), arr)
2010-12-28 10:12:45 +00:00
import Data.Typeable (Typeable)
import Data.Binary (Binary)
2010-12-25 18:37:21 +00:00
import Hakyll.Core.ResourceProvider
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
import Hakyll.Core.Compiler
import Hakyll.Core.Route
2010-12-28 10:12:45 +00:00
import Hakyll.Core.CompiledItem
import Hakyll.Core.Writable
2010-12-25 18:37:21 +00:00
-- | A collection of rules for the compilation process
--
2010-12-28 10:12:45 +00:00
data RuleSet = RuleSet
2010-12-25 18:37:21 +00:00
{ rulesRoute :: Route
2010-12-29 21:59:38 +00:00
, rulesCompilers :: [(Identifier, Compiler () CompiledItem)]
2010-12-25 18:37:21 +00:00
}
2010-12-28 10:12:45 +00:00
instance Monoid RuleSet where
2010-12-25 18:37:21 +00:00
mempty = RuleSet mempty mempty
mappend (RuleSet r1 c1) (RuleSet r2 c2) =
RuleSet (mappend r1 r2) (mappend c1 c2)
-- | The monad used to compose rules
--
2010-12-28 10:12:45 +00:00
newtype RulesM a = RulesM
{ unRulesM :: ReaderT ResourceProvider (Writer RuleSet) a
2010-12-25 18:37:21 +00:00
} deriving (Monad, Functor, Applicative)
-- | Simplification of the RulesM type; usually, it will not return any
-- result.
--
2010-12-28 10:12:45 +00:00
type Rules = RulesM ()
2010-12-25 18:37:21 +00:00
-- | Run a Rules monad, resulting in a 'RuleSet'
--
2010-12-28 10:12:45 +00:00
runRules :: Rules -> ResourceProvider -> RuleSet
2010-12-25 18:37:21 +00:00
runRules rules provider = execWriter $ runReaderT (unRulesM rules) provider
-- | Add a route
--
2010-12-28 10:12:45 +00:00
addRoute :: Route -> Rules
2010-12-25 18:37:21 +00:00
addRoute route' = RulesM $ tell $ RuleSet route' mempty
-- | Add a number of compilers
--
2010-12-28 10:12:45 +00:00
addCompilers :: (Binary a, Typeable a, Writable a)
2010-12-29 21:59:38 +00:00
=> [(Identifier, Compiler () a)]
2010-12-28 10:12:45 +00:00
-> Rules
addCompilers compilers = RulesM $ tell $ RuleSet mempty $
map (second boxCompiler) compilers
where
2010-12-29 21:59:38 +00:00
boxCompiler = (>>> arr compiledItem)
2010-12-25 18:37:21 +00:00
-- | Add a compilation rule
--
-- This instructs all resources matching the given pattern to be compiled using
-- the given compiler
--
2010-12-28 10:12:45 +00:00
compile :: (Binary a, Typeable a, Writable a)
2010-12-29 21:59:38 +00:00
=> Pattern -> Compiler () a -> Rules
2010-12-25 18:37:21 +00:00
compile pattern compiler = RulesM $ do
identifiers <- matches pattern . resourceList <$> ask
unRulesM $ addCompilers $ zip identifiers (repeat compiler)
-- | Add a compilation rule
--
-- This sets a compiler for the given identifier
--
2010-12-28 10:12:45 +00:00
create :: (Binary a, Typeable a, Writable a)
2010-12-29 21:59:38 +00:00
=> Identifier -> Compiler () a -> Rules
2010-12-25 18:37:21 +00:00
create identifier compiler = addCompilers [(identifier, compiler)]
-- | Add a route
--
2010-12-28 10:12:45 +00:00
route :: Pattern -> Route -> Rules
2010-12-25 18:37:21 +00:00
route pattern route' = addRoute $ ifMatch pattern route'