summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Compiler.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Core/Compiler.hs')
-rw-r--r--src/Hakyll/Core/Compiler.hs29
1 files changed, 18 insertions, 11 deletions
diff --git a/src/Hakyll/Core/Compiler.hs b/src/Hakyll/Core/Compiler.hs
index 4e8b642..60c8ecb 100644
--- a/src/Hakyll/Core/Compiler.hs
+++ b/src/Hakyll/Core/Compiler.hs
@@ -16,10 +16,14 @@ import Control.Monad.State (State, modify, runState)
import Control.Monad.Reader (ReaderT, ask, runReaderT)
import Data.Set (Set)
import qualified Data.Set as S
+import Data.Typeable (Typeable)
+import Data.Binary (Binary)
import Hakyll.Core.Identifier
import Hakyll.Core.Target
import Hakyll.Core.Target.Internal
+import Hakyll.Core.CompiledItem
+import Hakyll.Core.Writable
-- | A set of dependencies
--
@@ -27,7 +31,7 @@ type Dependencies = Set Identifier
-- | Add one dependency
--
-addDependency :: Identifier -> CompilerM a ()
+addDependency :: Identifier -> CompilerM ()
addDependency dependency = CompilerM $ modify $ addDependency'
where
addDependency' x = x
@@ -36,8 +40,8 @@ addDependency dependency = CompilerM $ modify $ addDependency'
-- | Environment in which a compiler runs
--
-data CompilerEnvironment a = CompilerEnvironment
- { compilerIdentifier :: Identifier -- ^ Target identifier
+data CompilerEnvironment = CompilerEnvironment
+ { compilerIdentifier :: Identifier -- ^ Target identifier
}
-- | State carried along by a compiler
@@ -48,18 +52,18 @@ data CompilerState = CompilerState
-- | The compiler monad
--
-newtype CompilerM a b = CompilerM
- { unCompilerM :: ReaderT (CompilerEnvironment a) (State CompilerState) b
+newtype CompilerM a = CompilerM
+ { unCompilerM :: ReaderT CompilerEnvironment (State CompilerState) a
} deriving (Monad, Functor, Applicative)
-- | Simplified type for a compiler generating a target (which covers most
-- cases)
--
-type Compiler a = CompilerM a (TargetM a a)
+type Compiler a = CompilerM (TargetM a)
-- | Run a compiler, yielding the resulting target and it's dependencies
--
-runCompiler :: Compiler a -> Identifier -> (TargetM a a, Dependencies)
+runCompiler :: Compiler a -> Identifier -> (TargetM a, Dependencies)
runCompiler compiler identifier = second compilerDependencies $
runState (runReaderT (unCompilerM compiler) env) state
where
@@ -69,15 +73,18 @@ runCompiler compiler identifier = second compilerDependencies $
-- | Require another target. Using this function ensures automatic handling of
-- dependencies
--
-require :: Identifier
+require :: (Binary a, Typeable a, Writable a)
+ => Identifier
-> Compiler a
require identifier = do
addDependency identifier
- return $ TargetM $ flip targetDependencyLookup identifier <$> ask
+ return $ TargetM $ do
+ lookup' <- targetDependencyLookup <$> ask
+ return $ unCompiledItem $ lookup' identifier
-- | Construct a target from a string, this string being the content of the
-- resource.
--
-compileFromString :: (String -> TargetM a a) -- ^ Function to create the target
- -> Compiler a -- ^ Resulting compiler
+compileFromString :: (String -> TargetM a) -- ^ Function to create the target
+ -> Compiler a -- ^ Resulting compiler
compileFromString = return . (getResourceString >>=)