hakyll/src/Hakyll/Core/Runtime.hs

279 lines
11 KiB
Haskell
Raw Normal View History

2012-11-13 14:10:01 +00:00
--------------------------------------------------------------------------------
module Hakyll.Core.Runtime
( run
) where
--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
2013-02-09 14:11:40 +00:00
import Control.Monad (unless)
2012-11-13 14:10:01 +00:00
import Control.Monad.Error (ErrorT, runErrorT, throwError)
import Control.Monad.Reader (ask)
import Control.Monad.RWS (RWST, runRWST)
import Control.Monad.State (get, modify)
import Control.Monad.Trans (liftIO)
2013-01-20 20:55:40 +00:00
import Data.List (intercalate)
2012-11-13 14:10:01 +00:00
import Data.Map (Map)
import qualified Data.Map as M
import Data.Monoid (mempty)
import Data.Set (Set)
import qualified Data.Set as S
2013-01-15 16:15:46 +00:00
import System.Exit (ExitCode (..))
2012-11-13 14:10:01 +00:00
import System.FilePath ((</>))
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler.Internal
2012-11-13 16:31:03 +00:00
import Hakyll.Core.Compiler.Require
2012-11-13 14:10:01 +00:00
import Hakyll.Core.Configuration
import Hakyll.Core.Dependencies
import Hakyll.Core.Identifier
import Hakyll.Core.Item
2012-11-18 20:56:52 +00:00
import Hakyll.Core.Item.SomeItem
import Hakyll.Core.Logger (Logger)
2012-11-14 10:17:28 +00:00
import qualified Hakyll.Core.Logger as Logger
2012-11-18 20:56:52 +00:00
import Hakyll.Core.Provider
2012-11-13 14:10:01 +00:00
import Hakyll.Core.Routes
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Store (Store)
import qualified Hakyll.Core.Store as Store
import Hakyll.Core.Util.File
import Hakyll.Core.Writable
--------------------------------------------------------------------------------
run :: Configuration -> Logger -> Rules a -> IO (ExitCode, RuleSet)
run config logger rules = do
2012-11-13 14:10:01 +00:00
-- Initialization
2012-11-14 12:32:31 +00:00
Logger.header logger "Initialising..."
Logger.message logger "Creating store..."
2012-11-21 19:38:13 +00:00
store <- Store.new (inMemoryCache config) $ storeDirectory config
2012-11-14 12:32:31 +00:00
Logger.message logger "Creating provider..."
2012-11-25 09:45:55 +00:00
provider <- newProvider store (shouldIgnoreFile config) $
providerDirectory config
2012-11-14 12:32:31 +00:00
Logger.message logger "Running rules..."
ruleSet <- runRules rules provider
2012-11-13 14:10:01 +00:00
-- Get old facts
mOldFacts <- Store.get store factsKey
let (oldFacts) = case mOldFacts of Store.Found f -> f
_ -> mempty
-- Build runtime read/state
let compilers = rulesCompilers ruleSet
read' = RuntimeRead
2012-11-21 19:38:13 +00:00
{ runtimeConfiguration = config
2012-11-13 14:10:01 +00:00
, runtimeLogger = logger
, runtimeProvider = provider
, runtimeStore = store
, runtimeRoutes = rulesRoutes ruleSet
, runtimeUniverse = M.fromList compilers
2012-11-13 14:10:01 +00:00
}
state = RuntimeState
2014-12-12 15:33:50 +00:00
{ runtimeDone = S.empty
, runtimeSnapshots = S.empty
, runtimeTodo = M.empty
, runtimeFacts = oldFacts
2012-11-13 14:10:01 +00:00
}
-- Run the program and fetch the resulting state
result <- runErrorT $ runRWST build read' state
case result of
Left e -> do
Logger.error logger e
Logger.flush logger
2013-01-15 16:15:46 +00:00
return (ExitFailure 1, ruleSet)
2012-11-13 14:10:01 +00:00
Right (_, s, _) -> do
Store.set store factsKey $ runtimeFacts s
2013-01-06 17:33:00 +00:00
Logger.debug logger "Removing tmp directory..."
removeDirectory $ tmpDirectory config
Logger.flush logger
2013-01-15 16:15:46 +00:00
return (ExitSuccess, ruleSet)
2012-11-13 14:10:01 +00:00
where
factsKey = ["Hakyll.Core.Runtime.run", "facts"]
--------------------------------------------------------------------------------
data RuntimeRead = RuntimeRead
{ runtimeConfiguration :: Configuration
, runtimeLogger :: Logger
2012-11-18 20:56:52 +00:00
, runtimeProvider :: Provider
2012-11-13 14:10:01 +00:00
, runtimeStore :: Store
, runtimeRoutes :: Routes
, runtimeUniverse :: Map Identifier (Compiler SomeItem)
2012-11-13 14:10:01 +00:00
}
--------------------------------------------------------------------------------
data RuntimeState = RuntimeState
2014-12-12 15:33:50 +00:00
{ runtimeDone :: Set Identifier
, runtimeSnapshots :: Set (Identifier, Snapshot)
, runtimeTodo :: Map Identifier (Compiler SomeItem)
, runtimeFacts :: DependencyFacts
2012-11-13 14:10:01 +00:00
}
--------------------------------------------------------------------------------
type Runtime a = RWST RuntimeRead () RuntimeState (ErrorT String IO) a
--------------------------------------------------------------------------------
build :: Runtime ()
build = do
2012-11-14 10:17:28 +00:00
logger <- runtimeLogger <$> ask
Logger.header logger "Checking for out-of-date items"
2012-11-13 14:10:01 +00:00
scheduleOutOfDate
2012-11-14 10:17:28 +00:00
Logger.header logger "Compiling"
2012-11-13 14:10:01 +00:00
pickAndChase
2012-11-14 10:17:28 +00:00
Logger.header logger "Success"
2012-11-13 14:10:01 +00:00
--------------------------------------------------------------------------------
scheduleOutOfDate :: Runtime ()
scheduleOutOfDate = do
2012-11-14 12:32:31 +00:00
logger <- runtimeLogger <$> ask
2012-11-13 14:10:01 +00:00
provider <- runtimeProvider <$> ask
universe <- runtimeUniverse <$> ask
facts <- runtimeFacts <$> get
todo <- runtimeTodo <$> get
let identifiers = M.keys universe
2013-02-09 14:11:40 +00:00
modified = S.fromList $ flip filter identifiers $
resourceModified provider
2012-11-14 12:32:31 +00:00
let (ood, facts', msgs) = outOfDate identifiers modified facts
todo' = M.filterWithKey
(\id' _ -> id' `S.member` ood) universe
2012-11-13 14:10:01 +00:00
2012-11-14 12:32:31 +00:00
-- Print messages
mapM_ (Logger.debug logger) msgs
2012-11-13 14:10:01 +00:00
-- Update facts and todo items
modify $ \s -> s
2012-11-13 18:03:58 +00:00
{ runtimeDone = runtimeDone s `S.union`
(S.fromList identifiers `S.difference` ood)
, runtimeTodo = todo `M.union` todo'
2012-11-13 14:10:01 +00:00
, runtimeFacts = facts'
}
--------------------------------------------------------------------------------
pickAndChase :: Runtime ()
pickAndChase = do
todo <- runtimeTodo <$> get
case M.minViewWithKey todo of
Nothing -> return ()
2012-11-13 18:03:58 +00:00
Just ((id', _), _) -> do
chase [] id'
pickAndChase
2012-11-13 14:10:01 +00:00
--------------------------------------------------------------------------------
chase :: [Identifier] -> Identifier -> Runtime ()
chase trail id'
2013-01-20 20:55:40 +00:00
| id' `elem` trail = throwError $ "Hakyll.Core.Runtime.chase: " ++
"Dependency cycle detected: " ++ intercalate " depends on "
(map show $ dropWhile (/= id') (reverse trail) ++ [id'])
2012-11-13 14:10:01 +00:00
| otherwise = do
logger <- runtimeLogger <$> ask
todo <- runtimeTodo <$> get
provider <- runtimeProvider <$> ask
universe <- runtimeUniverse <$> ask
routes <- runtimeRoutes <$> ask
store <- runtimeStore <$> ask
config <- runtimeConfiguration <$> ask
2012-11-29 11:04:57 +00:00
Logger.debug logger $ "Processing " ++ show id'
2012-11-13 14:10:01 +00:00
let compiler = todo M.! id'
2012-11-13 14:10:01 +00:00
read' = CompilerRead
2013-01-06 17:33:00 +00:00
{ compilerConfig = config
, compilerUnderlying = id'
2012-11-13 16:31:03 +00:00
, compilerProvider = provider
, compilerUniverse = M.keysSet universe
2012-11-13 16:31:03 +00:00
, compilerRoutes = routes
, compilerStore = store
, compilerLogger = logger
2012-11-13 14:10:01 +00:00
}
2012-11-14 10:17:28 +00:00
result <- liftIO $ runCompiler compiler read'
2012-11-13 14:10:01 +00:00
case result of
-- Rethrow error
CompilerError [] -> throwError
"Compiler failed but no info given, try running with -v?"
CompilerError es -> throwError $ intercalate "; " es
2012-11-13 14:10:01 +00:00
2014-12-12 15:33:50 +00:00
-- Signal that a snapshot was saved ->
CompilerSnapshot snapshot c -> do
-- Update info. The next 'chase' will pick us again at some
-- point so we can continue then.
2014-12-12 15:33:50 +00:00
modify $ \s -> s
{ runtimeSnapshots =
S.insert (id', snapshot) (runtimeSnapshots s)
, runtimeTodo = M.insert id' c (runtimeTodo s)
}
2012-11-13 14:10:01 +00:00
-- Huge success
2012-11-18 20:56:52 +00:00
CompilerDone (SomeItem item) cwrite -> do
-- Print some info
let facts = compilerDependencies cwrite
2012-11-14 10:17:28 +00:00
cacheHits
2012-11-14 12:32:31 +00:00
| compilerCacheHits cwrite <= 0 = "updated"
| otherwise = "cached "
Logger.message logger $ cacheHits ++ " " ++ show id'
2012-11-14 10:17:28 +00:00
-- Sanity check
unless (itemIdentifier item == id') $ throwError $
"The compiler yielded an Item with Identifier " ++
show (itemIdentifier item) ++ ", but we were expecting " ++
"an Item with Identifier " ++ show id' ++ " " ++
"(you probably want to call makeItem to solve this problem)"
2012-11-13 14:10:01 +00:00
-- Write if necessary
(mroute, _) <- liftIO $ runRoutes routes provider id'
2013-01-21 21:45:50 +00:00
case mroute of
Nothing -> return ()
Just route -> do
let path = destinationDirectory config </> route
2012-11-13 14:10:01 +00:00
liftIO $ makeDirectories path
2012-11-18 20:56:52 +00:00
liftIO $ write path item
2012-11-14 12:32:31 +00:00
Logger.debug logger $ "Routed to " ++ path
2012-11-13 14:10:01 +00:00
-- Save! (For load)
2012-11-24 09:56:19 +00:00
liftIO $ save store item
2012-11-13 16:31:03 +00:00
2012-11-13 14:10:01 +00:00
-- Update state
modify $ \s -> s
{ runtimeDone = S.insert id' (runtimeDone s)
, runtimeTodo = M.delete id' (runtimeTodo s)
, runtimeFacts = M.insert id' facts (runtimeFacts s)
}
-- Try something else first
CompilerRequire dep c -> do
-- Update the compiler so we don't execute it twice
2014-12-12 15:33:50 +00:00
let (depId, depSnapshot) = dep
done <- runtimeDone <$> get
snapshots <- runtimeSnapshots <$> get
-- Done if we either completed the entire item (runtimeDone) or
-- if we previously saved the snapshot (runtimeSnapshots).
let depDone =
depId `S.member` done ||
(depId, depSnapshot) `S.member` snapshots
2012-11-13 14:10:01 +00:00
modify $ \s -> s
{ runtimeTodo = M.insert id'
(if depDone then c else compilerResult result)
(runtimeTodo s)
}
-- If the required item is already compiled, continue, or, start
-- chasing that
2014-12-12 15:33:50 +00:00
Logger.debug logger $ "Require " ++ show depId ++
" (snapshot " ++ depSnapshot ++ "): " ++
(if depDone then "OK" else "chasing")
2014-12-12 15:33:50 +00:00
if depDone then chase trail id' else chase (id' : trail) depId