hakyll/src/Hakyll/Main.hs

178 lines
5.6 KiB
Haskell
Raw Normal View History

2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 10:34:00 +00:00
-- | Module providing the main hakyll function and command-line argument parsing
{-# LANGUAGE CPP #-}
2011-02-03 10:34:00 +00:00
module Hakyll.Main
( hakyll
, hakyllWith
) where
2011-02-03 13:18:09 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
import Control.Monad (when)
import System.Directory (doesDirectoryExist,
removeDirectoryRecursive)
import System.Environment (getArgs, getProgName)
import System.Process (system)
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2012-12-29 09:41:05 +00:00
import Hakyll.Check
2012-11-24 09:56:19 +00:00
import Hakyll.Core.Configuration
import Hakyll.Core.Rules
import Hakyll.Core.Runtime
--------------------------------------------------------------------------------
#ifdef PREVIEW_SERVER
import Control.Applicative ((<$>))
import Control.Concurrent (forkIO)
import qualified Data.Set as S
import Hakyll.Core.Identifier
import Hakyll.Core.Rules.Internal
2012-12-29 08:53:59 +00:00
import Hakyll.Preview.Poll
import Hakyll.Preview.Server
#endif
2011-02-03 10:34:00 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 10:34:00 +00:00
-- | This usualy is the function with which the user runs the hakyll compiler
2012-11-13 18:03:58 +00:00
hakyll :: Rules a -> IO ()
hakyll = hakyllWith defaultConfiguration
2011-02-03 10:34:00 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 10:34:00 +00:00
-- | A variant of 'hakyll' which allows the user to specify a custom
-- configuration
2012-11-13 18:03:58 +00:00
hakyllWith :: Configuration -> Rules a -> IO ()
2011-05-27 19:00:59 +00:00
hakyllWith conf rules = do
2011-02-03 13:18:09 +00:00
args <- getArgs
case args of
2011-05-27 19:00:59 +00:00
["build"] -> build conf rules
2012-12-29 09:41:05 +00:00
["check"] -> check conf
2011-05-27 19:00:59 +00:00
["clean"] -> clean conf
2011-02-03 13:18:09 +00:00
["help"] -> help
2011-05-27 19:00:59 +00:00
["preview"] -> preview conf rules 8000
["preview", p] -> preview conf rules (read p)
["rebuild"] -> rebuild conf rules
["server"] -> server conf 8000
["server", p] -> server conf (read p)
2011-06-15 06:53:47 +00:00
["deploy"] -> deploy conf
2011-02-03 13:18:09 +00:00
_ -> help
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 13:18:09 +00:00
-- | Build the site
2012-11-13 18:03:58 +00:00
build :: Configuration -> Rules a -> IO ()
2011-05-27 19:00:59 +00:00
build conf rules = do
_ <- run conf rules
return ()
2011-02-03 13:18:09 +00:00
2012-11-24 09:56:19 +00:00
2012-12-29 09:41:05 +00:00
--------------------------------------------------------------------------------
-- | Run the checker
check :: Configuration -> IO ()
check = runCheck
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 13:18:09 +00:00
-- | Remove the output directories
2012-11-13 18:03:58 +00:00
clean :: Configuration -> IO ()
2011-05-27 19:00:59 +00:00
clean conf = do
remove $ destinationDirectory conf
remove $ storeDirectory conf
2011-02-03 13:18:09 +00:00
where
remove dir = do
putStrLn $ "Removing " ++ dir ++ "..."
exists <- doesDirectoryExist dir
when exists $ removeDirectoryRecursive dir
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 13:18:09 +00:00
-- | Show usage information.
help :: IO ()
help = do
name <- getProgName
mapM_ putStrLn
[ "ABOUT"
, ""
, "This is a Hakyll site generator program. You should always"
, "run it from the project root directory."
, ""
, "USAGE"
, ""
, name ++ " build Generate the site"
, name ++ " clean Clean up and remove cache"
, name ++ " help Show this message"
, name ++ " preview [port] Run a server and autocompile"
, name ++ " rebuild Clean up and build again"
, name ++ " server [port] Run a local test server"
2011-06-15 06:53:47 +00:00
, name ++ " deploy Upload/deploy your site"
, ""
2011-02-03 13:18:09 +00:00
]
#ifndef PREVIEW_SERVER
previewServerDisabled
#endif
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-10 19:05:50 +00:00
-- | Preview the site
2012-11-13 18:03:58 +00:00
preview :: Configuration -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
2011-05-27 19:00:59 +00:00
preview conf rules port = do
2011-02-10 19:05:50 +00:00
-- Fork a thread polling for changes
2011-05-27 19:00:59 +00:00
_ <- forkIO $ previewPoll conf update
2012-11-13 18:03:58 +00:00
2011-02-10 19:05:50 +00:00
-- Run the server in the main thread
2011-05-27 19:00:59 +00:00
server conf port
where
2012-11-09 15:34:45 +00:00
update = map toFilePath . S.toList . rulesResources <$> run conf rules
#else
preview _ _ _ = previewServerDisabled
#endif
2011-02-10 19:05:50 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 13:18:09 +00:00
-- | Rebuild the site
2012-11-13 18:03:58 +00:00
rebuild :: Configuration -> Rules a -> IO ()
2011-05-27 19:00:59 +00:00
rebuild conf rules = do
clean conf
build conf rules
2011-02-03 13:18:09 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2011-02-03 13:18:09 +00:00
-- | Start a server
2012-11-13 18:03:58 +00:00
server :: Configuration -> Int -> IO ()
#ifdef PREVIEW_SERVER
2011-05-27 19:00:59 +00:00
server conf port = do
let destination = destinationDirectory conf
2011-02-03 13:18:09 +00:00
staticServer destination preServeHook port
where
preServeHook _ = return ()
#else
server _ _ = previewServerDisabled
#endif
2011-06-15 06:53:47 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
-- | Upload the site
2012-11-13 18:03:58 +00:00
deploy :: Configuration -> IO ()
2011-06-15 06:53:47 +00:00
deploy conf = do
_ <- system $ deployCommand conf
return ()
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
-- | Print a warning message about the preview serving not being enabled
#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