hakyll/src/Hakyll/Core/Compiler.hs

91 lines
2.6 KiB
Haskell
Raw Normal View History

2010-12-25 17:15:44 +00:00
-- | A Compiler manages targets and dependencies between targets.
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Compiler
( Dependencies
, CompilerM
, Compiler
, runCompiler
, require
2010-12-26 12:21:27 +00:00
, compileFromString
2010-12-25 17:15:44 +00:00
) where
import Control.Arrow (second)
import Control.Applicative (Applicative, (<$>))
import Control.Monad.State (State, modify, runState)
import Control.Monad.Reader (ReaderT, ask, runReaderT)
import Data.Set (Set)
import qualified Data.Set as S
2010-12-28 10:12:45 +00:00
import Data.Typeable (Typeable)
import Data.Binary (Binary)
2010-12-25 17:15:44 +00:00
import Hakyll.Core.Identifier
2010-12-26 10:57:42 +00:00
import Hakyll.Core.Target
2010-12-25 17:15:44 +00:00
import Hakyll.Core.Target.Internal
2010-12-28 10:12:45 +00:00
import Hakyll.Core.CompiledItem
import Hakyll.Core.Writable
2010-12-25 17:15:44 +00:00
-- | A set of dependencies
--
type Dependencies = Set Identifier
-- | Add one dependency
--
2010-12-28 10:12:45 +00:00
addDependency :: Identifier -> CompilerM ()
2010-12-25 17:15:44 +00:00
addDependency dependency = CompilerM $ modify $ addDependency'
where
addDependency' x = x
{ compilerDependencies = S.insert dependency $ compilerDependencies x
}
-- | Environment in which a compiler runs
--
2010-12-28 10:12:45 +00:00
data CompilerEnvironment = CompilerEnvironment
{ compilerIdentifier :: Identifier -- ^ Target identifier
2010-12-25 17:15:44 +00:00
}
-- | State carried along by a compiler
--
data CompilerState = CompilerState
{ compilerDependencies :: Dependencies
}
-- | The compiler monad
--
2010-12-28 10:12:45 +00:00
newtype CompilerM a = CompilerM
{ unCompilerM :: ReaderT CompilerEnvironment (State CompilerState) a
2010-12-25 17:15:44 +00:00
} deriving (Monad, Functor, Applicative)
-- | Simplified type for a compiler generating a target (which covers most
-- cases)
--
2010-12-28 10:12:45 +00:00
type Compiler a = CompilerM (TargetM a)
2010-12-25 17:15:44 +00:00
-- | Run a compiler, yielding the resulting target and it's dependencies
--
2010-12-28 10:12:45 +00:00
runCompiler :: Compiler a -> Identifier -> (TargetM a, Dependencies)
2010-12-25 17:15:44 +00:00
runCompiler compiler identifier = second compilerDependencies $
runState (runReaderT (unCompilerM compiler) env) state
where
env = CompilerEnvironment {compilerIdentifier = identifier}
state = CompilerState S.empty
-- | Require another target. Using this function ensures automatic handling of
-- dependencies
--
2010-12-28 10:12:45 +00:00
require :: (Binary a, Typeable a, Writable a)
=> Identifier
2010-12-25 17:15:44 +00:00
-> Compiler a
require identifier = do
addDependency identifier
2010-12-28 10:12:45 +00:00
return $ TargetM $ do
lookup' <- targetDependencyLookup <$> ask
return $ unCompiledItem $ lookup' identifier
2010-12-25 17:15:44 +00:00
2010-12-26 10:57:42 +00:00
-- | Construct a target from a string, this string being the content of the
-- resource.
--
2010-12-28 10:12:45 +00:00
compileFromString :: (String -> TargetM a) -- ^ Function to create the target
-> Compiler a -- ^ Resulting compiler
2010-12-26 12:21:27 +00:00
compileFromString = return . (getResourceString >>=)