summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Run.hs
blob: 31280db3cf4b92748537a442742b103563054530 (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
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
-- | This is the module which binds it all together
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Run where

import Control.Applicative
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Trans
import Control.Arrow ((&&&))
import Control.Monad (foldM, forM_, forM, filterM)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Monoid (mempty)
import Data.Typeable (Typeable)
import Data.Binary (Binary)
import System.FilePath ((</>))
import Control.Applicative ((<$>))
import Data.Set (Set)
import qualified Data.Set as S

import Hakyll.Core.Route
import Hakyll.Core.Identifier
import Hakyll.Core.Util.File
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.ResourceProvider
import Hakyll.Core.ResourceProvider.FileResourceProvider
import Hakyll.Core.Rules
import Hakyll.Core.DirectedGraph
import Hakyll.Core.DirectedGraph.Dot
import Hakyll.Core.DirectedGraph.DependencySolver
import Hakyll.Core.DirectedGraph.ObsoleteFilter
import Hakyll.Core.Writable
import Hakyll.Core.Store
import Hakyll.Core.CompiledItem

hakyll :: Rules -> IO ()
hakyll rules = do
    store <- makeStore "_store"
    provider <- fileResourceProvider
    let ruleSet = runRules rules provider
        compilers = rulesCompilers ruleSet
    runReaderT (unHakyll (addNewCompilers [] compilers)) $
        env ruleSet provider store
  where
    env ruleSet provider store = HakyllEnvironment
        { hakyllRoute            = rulesRoute ruleSet
        , hakyllResourceProvider = provider
        , hakyllStore            = store
        , hakyllModified         = S.empty
        }

data HakyllEnvironment = HakyllEnvironment
    { hakyllRoute            :: Route
    , hakyllResourceProvider :: ResourceProvider
    , hakyllStore            :: Store
    , hakyllModified         :: Set Identifier
    }

newtype Hakyll a = Hakyll
    { unHakyll :: ReaderT HakyllEnvironment IO a
    } deriving (Functor, Applicative, Monad)

-- | Return a set of modified identifiers
--
modified :: ResourceProvider     -- ^ Resource provider
         -> Store                -- ^ Store
         -> [Identifier]         -- ^ Identifiers to check
         -> IO (Set Identifier)  -- ^ Modified resources
modified provider store ids = fmap S.fromList $ flip filterM ids $ \id' ->
    if resourceExists provider id' then resourceModified provider id' store
                                   else return False

-- | Add a number of compilers and continue using these compilers
--
addNewCompilers :: [(Identifier, Compiler () CompileRule)]
                -- ^ Remaining compilers yet to be run
                -> [(Identifier, Compiler () CompileRule)]
                -- ^ Compilers to add
                -> Hakyll ()
addNewCompilers oldCompilers newCompilers = Hakyll $ do
    -- Get some information
    provider <- hakyllResourceProvider <$> ask
    store <- hakyllStore <$> ask

    let -- All compilers
        compilers = oldCompilers ++ newCompilers

        -- Get all dependencies for the compilers
        dependencies = flip map compilers $ \(id', compiler) ->
            let deps = runCompilerDependencies compiler provider
            in (id', deps)

        -- Create a compiler map (Id -> Compiler)
        compilerMap = M.fromList compilers

        -- Create the dependency graph
        graph = fromList dependencies

    -- Check which items are up-to-date. This only needs to happen for the new
    -- compilers
    modified' <- liftIO $ modified provider store $ map fst compilers

    let -- Try to reduce the graph using this modified information
        reducedGraph = filterObsolete modified' graph

    let -- Solve the graph
        ordered = solveDependencies reducedGraph

        -- Join the order with the compilers again
        orderedCompilers = map (id &&& (compilerMap M.!)) ordered

    -- Now run the ordered list of compilers
    local (updateModified modified') $ unHakyll $ runCompilers orderedCompilers
  where
    -- Add the modified information for the new compilers
    updateModified modified' env = env
        { hakyllModified = hakyllModified env `S.union` modified'
        }

runCompilers :: [(Identifier, Compiler () CompileRule)]
             -- ^ Ordered list of compilers
             -> Hakyll ()
             -- ^ No result
runCompilers [] = return ()
runCompilers ((id', compiler) : compilers) = Hakyll $ do
    -- Obtain information
    route' <- hakyllRoute <$> ask
    provider <- hakyllResourceProvider <$> ask
    store <- hakyllStore <$> ask
    modified' <- hakyllModified <$> ask

    let -- Determine the URL
        url = runRoute route' id'
    
        -- Check if the resource was modified
        isModified = id' `S.member` modified'

    -- Run the compiler
    result <- liftIO $ runCompiler compiler id' provider url store isModified
    liftIO $ putStrLn $ "Generated target: " ++ show id'

    let CompileRule compiled = result

    case url of
        Nothing -> return ()
        Just r  -> liftIO $ do
            putStrLn $ "Routing " ++ show id' ++ " to " ++ r
            let path = "_site" </> r
            makeDirectories path
            write path compiled

    liftIO $ putStrLn ""

    -- Continue for the remaining compilers
    unHakyll $ runCompilers compilers