summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Compiler.hs
blob: 70006e9365ee46de6818b671a1fe32a335a645e2 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
-- | A Compiler manages targets and dependencies between targets.
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Compiler
    ( Dependencies
    , CompilerM
    , Compiler
    , runCompiler
    , require
    , target
    , targetFromString
    ) 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

import Hakyll.Core.Identifier
import Hakyll.Core.Target
import Hakyll.Core.Target.Internal

-- | A set of dependencies
--
type Dependencies = Set Identifier

-- | Add one dependency
--
addDependency :: Identifier -> CompilerM a ()
addDependency dependency = CompilerM $ modify $ addDependency'
  where
    addDependency' x = x
        { compilerDependencies = S.insert dependency $ compilerDependencies x
        }

-- | Environment in which a compiler runs
--
data CompilerEnvironment a = CompilerEnvironment
    { compilerIdentifier :: Identifier -- ^ Target identifier
    }

-- | State carried along by a compiler
--
data CompilerState = CompilerState
    { compilerDependencies :: Dependencies
    }

-- | The compiler monad
--
newtype CompilerM a b = CompilerM
    { unCompilerM :: ReaderT (CompilerEnvironment a) (State CompilerState) b
    } deriving (Monad, Functor, Applicative)

-- | Simplified type for a compiler generating a target (which covers most
-- cases)
--
type Compiler a = CompilerM a (TargetM a a)

-- | Run a compiler, yielding the resulting target and it's dependencies
--
runCompiler :: Compiler a -> Identifier -> (TargetM a a, Dependencies)
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
--
require :: Identifier
        -> Compiler a
require identifier = do
    addDependency identifier
    return $ TargetM $ flip targetDependencyLookup identifier <$> ask

-- | Construct a target inside a compiler
--
target :: TargetM a a -> Compiler a
target = return

-- | Construct a target from a string, this string being the content of the
-- resource.
--
targetFromString :: (String -> TargetM a a)  -- ^ Function to create the target
                 -> Compiler a               -- ^ Resulting compiler
targetFromString = target . (getResourceString >>=)