{-# LANGUAGE CPP #-}
module Hakyll.Commands
( Check(..)
, build
, check
, clean
, preview
, rebuild
, server
, deploy
, watch
) where
import Control.Concurrent
import System.Exit (ExitCode)
import Hakyll.Check (Check(..))
import qualified Hakyll.Check as Check
import Hakyll.Core.Configuration
import Hakyll.Core.Logger (Logger)
import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Rules
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Runtime
import Hakyll.Core.Util.File
#ifdef WATCH_SERVER
import Hakyll.Preview.Poll (watchUpdates)
#endif
#ifdef PREVIEW_SERVER
import Hakyll.Preview.Server
#endif
#ifdef mingw32_HOST_OS
import Control.Monad (void)
import System.IO.Error (catchIOError)
#endif
build :: RunMode -> Configuration -> Logger -> Rules a -> IO ExitCode
build :: forall a.
RunMode -> Configuration -> Logger -> Rules a -> IO ExitCode
build RunMode
mode Configuration
conf Logger
logger Rules a
rules = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
RunMode
-> Configuration -> Logger -> Rules a -> IO (ExitCode, RuleSet)
run RunMode
mode Configuration
conf Logger
logger Rules a
rules
check :: Configuration -> Logger -> Check.Check -> IO ExitCode
check :: Configuration -> Logger -> Check -> IO ExitCode
check = Configuration -> Logger -> Check -> IO ExitCode
Check.check
clean :: Configuration -> Logger -> IO ()
clean :: Configuration -> Logger -> IO ()
clean Configuration
conf Logger
logger = do
[Char] -> IO ()
remove forall a b. (a -> b) -> a -> b
$ Configuration -> [Char]
destinationDirectory Configuration
conf
[Char] -> IO ()
remove forall a b. (a -> b) -> a -> b
$ Configuration -> [Char]
storeDirectory Configuration
conf
[Char] -> IO ()
remove forall a b. (a -> b) -> a -> b
$ Configuration -> [Char]
tmpDirectory Configuration
conf
where
remove :: [Char] -> IO ()
remove [Char]
dir = do
forall (m :: * -> *). MonadIO m => Logger -> [Char] -> m ()
Logger.header Logger
logger forall a b. (a -> b) -> a -> b
$ [Char]
"Removing " forall a. [a] -> [a] -> [a]
++ [Char]
dir forall a. [a] -> [a] -> [a]
++ [Char]
"..."
[Char] -> IO ()
removeDirectory [Char]
dir
preview :: Configuration -> Logger -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
preview :: forall a. Configuration -> Logger -> Rules a -> Int -> IO ()
preview Configuration
conf Logger
logger Rules a
rules Int
port = do
IO ()
deprecatedMessage
forall a.
Configuration
-> Logger -> [Char] -> Int -> Bool -> Rules a -> IO ()
watch Configuration
conf Logger
logger [Char]
"0.0.0.0" Int
port Bool
True Rules a
rules
where
deprecatedMessage :: IO ()
deprecatedMessage = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ [Char] -> IO ()
putStrLn [ [Char]
"The preview command has been deprecated."
, [Char]
"Use the watch command for recompilation and serving."
]
#else
preview _ _ _ _ = previewServerDisabled
#endif
watch :: Configuration -> Logger -> String -> Int -> Bool -> Rules a -> IO ()
#ifdef WATCH_SERVER
watch :: forall a.
Configuration
-> Logger -> [Char] -> Int -> Bool -> Rules a -> IO ()
watch Configuration
conf Logger
logger [Char]
host Int
port Bool
runServer Rules a
rules = do
#ifndef mingw32_HOST_OS
ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ Configuration -> IO Pattern -> IO ()
watchUpdates Configuration
conf IO Pattern
update
#else
catchIOError (void $ forkOS $ watchUpdates conf update) $ \_ -> do
fail $ "Hakyll.Commands.watch: Could not start update watching " ++
"thread. Did you compile with -threaded flag?"
#endif
IO ()
server'
where
update :: IO Pattern
update = do
(ExitCode
_, RuleSet
ruleSet) <- forall a.
RunMode
-> Configuration -> Logger -> Rules a -> IO (ExitCode, RuleSet)
run RunMode
RunModeNormal Configuration
conf Logger
logger Rules a
rules
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ RuleSet -> Pattern
rulesPattern RuleSet
ruleSet
loop :: IO b
loop = Int -> IO ()
threadDelay Int
100000 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO b
loop
server' :: IO ()
server' = if Bool
runServer then Configuration -> Logger -> [Char] -> Int -> IO ()
server Configuration
conf Logger
logger [Char]
host Int
port else forall {b}. IO b
loop
#else
watch _ _ _ _ _ _ = watchServerDisabled
#endif
rebuild :: Configuration -> Logger -> Rules a -> IO ExitCode
rebuild :: forall a. Configuration -> Logger -> Rules a -> IO ExitCode
rebuild Configuration
conf Logger
logger Rules a
rules =
Configuration -> Logger -> IO ()
clean Configuration
conf Logger
logger forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a.
RunMode -> Configuration -> Logger -> Rules a -> IO ExitCode
build RunMode
RunModeNormal Configuration
conf Logger
logger Rules a
rules
server :: Configuration -> Logger -> String -> Int -> IO ()
#ifdef PREVIEW_SERVER
server :: Configuration -> Logger -> [Char] -> Int -> IO ()
server Configuration
conf Logger
logger [Char]
host Int
port = do
let settings :: StaticSettings
settings = Configuration -> [Char] -> StaticSettings
previewSettings Configuration
conf forall a b. (a -> b) -> a -> b
$ Configuration -> [Char]
destinationDirectory Configuration
conf
Logger -> StaticSettings -> [Char] -> Int -> IO ()
staticServer Logger
logger StaticSettings
settings [Char]
host Int
port
#else
server _ _ _ _ = previewServerDisabled
#endif
deploy :: Configuration -> IO ExitCode
deploy :: Configuration -> IO ExitCode
deploy Configuration
conf = Configuration -> Configuration -> IO ExitCode
deploySite Configuration
conf Configuration
conf
#ifndef PREVIEW_SERVER
previewServerDisabled :: IO ()
previewServerDisabled =
mapM_ putStrLn
[ "PREVIEW SERVER"
, ""
, "The preview server is not enabled in the version of Hakyll. To"
, "enable it, set the flag to True and recompile Hakyll."
, "Alternatively, use an external tool to serve your site directory."
]
#endif
#ifndef WATCH_SERVER
watchServerDisabled :: IO ()
watchServerDisabled =
mapM_ putStrLn
[ "WATCH SERVER"
, ""
, "The watch server is not enabled in the version of Hakyll. To"
, "enable it, set the flag to True and recompile Hakyll."
, "Alternatively, use an external tool to serve your site directory."
]
#endif