hakyll/src/Hakyll/Main.hs

123 lines
5.2 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 #-}
{-# LANGUAGE DeriveDataTypeable #-}
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 System.Console.CmdArgs
import qualified System.Console.CmdArgs.Explicit as CA
import System.Environment (getProgName)
import System.IO.Unsafe (unsafePerformIO)
import System.Exit (exitWith)
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
2012-12-31 14:32:46 +00:00
import qualified Hakyll.Check as Check
import qualified Hakyll.Commands as Commands
import qualified Hakyll.Core.Configuration as Config
import qualified Hakyll.Core.Logger as Logger
2012-11-24 09:56:19 +00:00
import Hakyll.Core.Rules
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 Config.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
hakyllWith :: Config.Configuration -> Rules a -> IO ()
2011-05-27 19:00:59 +00:00
hakyllWith conf rules = do
args' <- cmdArgs (hakyllArgs conf)
2012-11-24 09:56:19 +00:00
2012-12-31 14:16:14 +00:00
let verbosity' = if verbose args' then Logger.Debug else Logger.Message
2012-12-31 14:32:46 +00:00
check' =
if internal_links args' then Check.InternalLinks else Check.All
case args' of
Build _ -> Commands.build conf verbosity' rules >>= exitWith
Check _ _ -> Commands.check conf verbosity' check'
Clean _ -> Commands.clean conf
Deploy _ -> Commands.deploy conf >>= exitWith
Help _ -> showHelp
Preview _ p -> Commands.preview conf verbosity' rules p
Rebuild _ -> Commands.rebuild conf verbosity' rules >>= exitWith
2014-03-24 08:33:24 +00:00
Server _ _ _ -> Commands.server conf (host args') (port args')
Watch _ _ p s -> Commands.watch conf verbosity' (host args') p (not s) 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
-- | Show usage information.
showHelp :: IO ()
showHelp = print $ CA.helpText [] CA.HelpFormatOne $ cmdArgsMode (hakyllArgs Config.defaultConfiguration)
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
data HakyllArgs
= Build {verbose :: Bool}
2012-12-31 14:32:46 +00:00
| Check {verbose :: Bool, internal_links :: Bool}
| Clean {verbose :: Bool}
| Deploy {verbose :: Bool}
| Help {verbose :: Bool}
| Preview {verbose :: Bool, port :: Int}
| Rebuild {verbose :: Bool}
2014-03-24 08:33:24 +00:00
| Server {verbose :: Bool, host :: String, port :: Int}
| Watch {verbose :: Bool, host :: String, port :: Int, no_server :: Bool }
deriving (Data, Typeable, Show)
2011-02-10 19:05:50 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
hakyllArgs :: Config.Configuration -> HakyllArgs
hakyllArgs conf = modes
[ (Build $ verboseFlag def) &= help "Generate the site"
2012-12-31 14:32:46 +00:00
, (Check (verboseFlag def) (False &= help "Check internal links only")) &=
help "Validate the site output"
, (Clean $ verboseFlag def) &= help "Clean up and remove cache"
, (Deploy $ verboseFlag def) &= help "Upload/deploy your site"
, (Help $ verboseFlag def) &= help "Show this message" &= auto
, (Preview (verboseFlag def) (portFlag defaultPort)) &=
help "[Deprecated] Please use the watch command"
, (Rebuild $ verboseFlag def) &= help "Clean and build again"
2014-03-24 08:33:24 +00:00
, (Server (verboseFlag def) (hostFlag defaultHost) (portFlag defaultPort)) &=
help "Start a preview server"
2014-03-24 08:33:24 +00:00
, (Watch (verboseFlag def) (hostFlag defaultHost) (portFlag defaultPort) (noServerFlag False) &=
help "Autocompile on changes and start a preview server. You can watch and recompile without running a server with --no-server.")
] &= help "Hakyll static site compiler" &= program progName
2014-03-24 08:33:24 +00:00
where
defaultHost = Config.previewHost conf
defaultPort = Config.previewPort conf
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
verboseFlag :: Data a => a -> a
verboseFlag x = x &= help "Run in verbose mode"
{-# INLINE verboseFlag #-}
2011-06-15 06:53:47 +00:00
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
noServerFlag :: Data a => a -> a
noServerFlag x = x &= help "Disable the built-in web server"
{-# INLINE noServerFlag #-}
2014-03-24 08:33:24 +00:00
--------------------------------------------------------------------------------
hostFlag :: Data a => a -> a
hostFlag x = x &= help "Host to serve on"
{-# INLINE hostFlag #-}
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
portFlag :: Data a => a -> a
portFlag x = x &= help "Port to listen on"
{-# INLINE portFlag #-}
2012-11-24 09:56:19 +00:00
--------------------------------------------------------------------------------
-- | This is necessary because not everyone calls their program the same...
progName :: String
progName = unsafePerformIO getProgName
{-# NOINLINE progName #-}