hakyll/src/Hakyll/Core/Rules/Internal.hs

95 lines
3.3 KiB
Haskell
Raw Normal View History

2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
-- | Internal rules module for types which are not exposed to the user
2012-11-08 12:50:08 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE Rank2Types #-}
2011-02-11 12:30:55 +00:00
module Hakyll.Core.Rules.Internal
2012-11-10 18:56:45 +00:00
( RuleSet (..)
2011-02-11 12:30:55 +00:00
, RuleState (..)
, RuleEnvironment (..)
2012-11-13 12:13:17 +00:00
, Rules (..)
2011-02-11 12:30:55 +00:00
, runRules
) where
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
import Control.Applicative (Applicative)
import Control.Monad.RWS (RWST, runRWST)
import qualified Data.Map as M
import Data.Monoid (Monoid, mappend, mempty)
import Data.Set (Set)
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
2012-11-18 20:56:52 +00:00
import Hakyll.Core.Item.SomeItem
import Hakyll.Core.Provider
2012-11-08 12:50:08 +00:00
import Hakyll.Core.Routes
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
-- | A collection of rules for the compilation process
data RuleSet = RuleSet
2011-02-15 17:32:55 +00:00
{ -- | Routes used in the compilation structure
rulesRoutes :: Routes
, -- | Compilation rules
2012-11-18 20:56:52 +00:00
rulesCompilers :: [(Identifier, Compiler SomeItem)]
2012-11-09 15:34:45 +00:00
, -- | A set of the actually used files
2012-11-13 12:13:17 +00:00
rulesResources :: Set Identifier
2011-02-11 12:30:55 +00:00
}
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
instance Monoid RuleSet where
2011-02-15 17:32:55 +00:00
mempty = RuleSet mempty mempty mempty
mappend (RuleSet r1 c1 s1) (RuleSet r2 c2 s2) =
RuleSet (mappend r1 r2) (mappend c1 c2) (mappend s1 s2)
2011-02-11 12:30:55 +00:00
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
-- | Rule state
data RuleState = RuleState
{ rulesNextIdentifier :: Int
2011-02-11 12:30:55 +00:00
} deriving (Show)
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
-- | Rule environment
data RuleEnvironment = RuleEnvironment
2012-11-18 20:56:52 +00:00
{ rulesProvider :: Provider
, rulesPattern :: Pattern
, rulesVersion :: Maybe String
}
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
-- | The monad used to compose rules
2012-11-13 12:13:17 +00:00
newtype Rules a = Rules
{ unRules :: RWST RuleEnvironment RuleSet RuleState IO a
2011-02-11 12:30:55 +00:00
} deriving (Monad, Functor, Applicative)
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-02-11 12:30:55 +00:00
-- | Run a Rules monad, resulting in a 'RuleSet'
2012-11-18 20:56:52 +00:00
runRules :: Rules a -> Provider -> IO RuleSet
2012-11-08 12:50:08 +00:00
runRules rules provider = do
2012-11-13 12:13:17 +00:00
(_, _, ruleSet) <- runRWST (unRules rules) env state
2012-11-08 12:50:08 +00:00
return $ nubCompilers ruleSet
2011-02-11 12:30:55 +00:00
where
state = RuleState {rulesNextIdentifier = 0}
2012-11-08 12:50:08 +00:00
env = RuleEnvironment
2012-11-18 20:56:52 +00:00
{ rulesProvider = provider
, rulesPattern = mempty
, rulesVersion = Nothing
2012-11-08 12:50:08 +00:00
}
2011-04-13 15:42:57 +00:00
2012-11-08 12:50:08 +00:00
--------------------------------------------------------------------------------
2011-04-13 15:42:57 +00:00
-- | Remove duplicate compilers from the 'RuleSet'. When two compilers match an
-- item, we prefer the first one
nubCompilers :: RuleSet -> RuleSet
nubCompilers set = set { rulesCompilers = nubCompilers' (rulesCompilers set) }
where
nubCompilers' = M.toList . M.fromListWith (flip const)