hakyll/src/Hakyll/Core/Rules.hs

156 lines
4.8 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
--
2011-01-30 09:44:42 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-}
2010-12-25 18:37:21 +00:00
module Hakyll.Core.Rules
2011-01-07 11:12:13 +00:00
( CompileRule (..)
, RuleSet (..)
2010-12-25 18:37:21 +00:00
, RulesM
, Rules
, runRules
, compile
, create
, route
2011-01-30 09:44:42 +00:00
, metaCompile
, metaCompileWith
2010-12-25 18:37:21 +00:00
) where
import Control.Applicative (Applicative, (<$>))
2011-02-11 07:39:10 +00:00
import Control.Monad.Writer (WriterT, execWriterT, tell)
import Control.Monad.Reader (ReaderT, runReaderT, ask)
2011-01-07 11:12:13 +00:00
import Control.Arrow (second, (>>>), arr, (>>^))
2011-02-11 07:39:10 +00:00
import Control.Monad.State (State, evalState, get, put)
import Data.Monoid (Monoid, mempty, mappend)
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
2011-01-07 11:12:13 +00:00
import Hakyll.Core.Compiler.Internal
2011-02-03 15:07:49 +00:00
import Hakyll.Core.Routes
2010-12-28 10:12:45 +00:00
import Hakyll.Core.CompiledItem
import Hakyll.Core.Writable
2010-12-25 18:37:21 +00:00
2011-01-07 11:12:13 +00:00
-- | 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.
--
2011-01-07 13:34:31 +00:00
data CompileRule = CompileRule CompiledItem
| MetaCompileRule [(Identifier, Compiler () CompileRule)]
2011-01-07 11:12:13 +00:00
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
2011-02-03 15:07:49 +00:00
{ rulesRoutes :: Routes
2011-01-07 11:12:13 +00:00
, rulesCompilers :: [(Identifier, Compiler () CompileRule)]
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)
2011-01-30 09:44:42 +00:00
-- | Rule state
--
data RuleState = RuleState
{ rulesMetaCompilerIndex :: Int
} deriving (Show)
2010-12-25 18:37:21 +00:00
-- | The monad used to compose rules
--
2010-12-28 10:12:45 +00:00
newtype RulesM a = RulesM
2011-01-30 09:44:42 +00:00
{ unRulesM :: ReaderT ResourceProvider (WriterT RuleSet (State RuleState)) 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
2011-01-30 09:44:42 +00:00
runRules rules provider =
evalState (execWriterT $ runReaderT (unRulesM rules) provider) state
where
state = RuleState {rulesMetaCompilerIndex = 0}
2010-12-25 18:37:21 +00:00
-- | Add a route
--
2011-02-03 15:07:49 +00:00
tellRoute :: Routes -> Rules
2011-01-07 11:12:13 +00:00
tellRoute route' = RulesM $ tell $ RuleSet route' mempty
2010-12-25 18:37:21 +00:00
-- | Add a number of compilers
--
2011-01-07 11:12:13 +00:00
tellCompilers :: (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
2011-01-07 11:12:13 +00:00
tellCompilers compilers = RulesM $ tell $ RuleSet mempty $
2010-12-28 10:12:45 +00:00
map (second boxCompiler) compilers
where
2011-01-07 13:34:31 +00:00
boxCompiler = (>>> arr compiledItem >>> arr CompileRule)
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
2011-01-07 11:12:13 +00:00
unRulesM $ tellCompilers $ zip identifiers (repeat compiler)
2010-12-25 18:37:21 +00:00
-- | 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
2011-01-07 11:12:13 +00:00
create identifier compiler = tellCompilers [(identifier, compiler)]
2010-12-25 18:37:21 +00:00
-- | Add a route
--
2011-02-03 15:07:49 +00:00
route :: Pattern -> Routes -> Rules
2011-01-07 11:12:13 +00:00
route pattern route' = tellRoute $ ifMatch pattern route'
-- | Add a compiler that produces other compilers over time
--
2011-01-30 09:44:42 +00:00
metaCompile :: (Binary a, Typeable a, Writable a)
=> Compiler () [(Identifier, Compiler () a)]
-- ^ Compiler generating the other compilers
-> Rules
-- ^ Resulting rules
metaCompile compiler = RulesM $ do
-- Create an identifier from the state
state <- get
let index = rulesMetaCompilerIndex state
id' = fromCaptureString "Hakyll.Core.Rules.metaCompile/*" (show index)
-- Update the state with a new identifier
put $ state {rulesMetaCompilerIndex = index + 1}
-- Fallback to 'metaCompileWith' with now known identifier
unRulesM $ metaCompileWith id' compiler
-- | Version of 'metaCompile' that allows you to specify a custom identifier for
-- the metacompiler.
--
metaCompileWith :: (Binary a, Typeable a, Writable a)
=> Identifier
-- ^ Identifier for this compiler
-> Compiler () [(Identifier, Compiler () a)]
-- ^ Compiler generating the other compilers
-> Rules
-- ^ Resulting rules
metaCompileWith identifier compiler = RulesM $ tell $ RuleSet mempty
2011-01-07 18:17:14 +00:00
[(identifier, compiler >>> arr makeRule )]
2011-01-07 11:12:13 +00:00
where
2011-01-07 18:17:14 +00:00
makeRule = MetaCompileRule . map (second box)
box = (>>> fromDependency identifier >>^ CompileRule . compiledItem)