{-# LANGUAGE CPP #-}
module Hakyll.Main
(
hakyll
, hakyllWith
, hakyllWithArgs
, hakyllWithExitCode
, hakyllWithExitCodeAndArgs
, Options(..)
, Command(..)
, optionParser
, commandParser
, defaultParser
, defaultParserPure
, defaultParserPrefs
, defaultParserInfo
) where
import System.Environment (getProgName)
import System.Exit (ExitCode (ExitSuccess), exitWith)
import System.IO.Unsafe (unsafePerformIO)
import Data.Monoid ((<>))
import qualified Options.Applicative as OA
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
import Hakyll.Core.Rules
hakyll :: Rules a -> IO ()
hakyll :: Rules a -> IO ()
hakyll = Configuration -> Rules a -> IO ()
forall a. Configuration -> Rules a -> IO ()
hakyllWith Configuration
Config.defaultConfiguration
hakyllWith :: Config.Configuration -> Rules a -> IO ()
hakyllWith :: Configuration -> Rules a -> IO ()
hakyllWith Configuration
conf Rules a
rules = Configuration -> Rules a -> IO ExitCode
forall a. Configuration -> Rules a -> IO ExitCode
hakyllWithExitCode Configuration
conf Rules a
rules IO ExitCode -> (ExitCode -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith
hakyllWithExitCode :: Config.Configuration -> Rules a -> IO ExitCode
hakyllWithExitCode :: Configuration -> Rules a -> IO ExitCode
hakyllWithExitCode Configuration
conf Rules a
rules = do
Options
args <- Configuration -> IO Options
defaultParser Configuration
conf
Configuration -> Options -> Rules a -> IO ExitCode
forall a. Configuration -> Options -> Rules a -> IO ExitCode
hakyllWithExitCodeAndArgs Configuration
conf Options
args Rules a
rules
hakyllWithArgs :: Config.Configuration -> Options -> Rules a -> IO ()
hakyllWithArgs :: Configuration -> Options -> Rules a -> IO ()
hakyllWithArgs Configuration
conf Options
args Rules a
rules =
Configuration -> Options -> Rules a -> IO ExitCode
forall a. Configuration -> Options -> Rules a -> IO ExitCode
hakyllWithExitCodeAndArgs Configuration
conf Options
args Rules a
rules IO ExitCode -> (ExitCode -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith
hakyllWithExitCodeAndArgs :: Config.Configuration ->
Options -> Rules a -> IO ExitCode
hakyllWithExitCodeAndArgs :: Configuration -> Options -> Rules a -> IO ExitCode
hakyllWithExitCodeAndArgs Configuration
conf Options
args Rules a
rules = do
let args' :: Command
args' = Options -> Command
optCommand Options
args
verbosity' :: Verbosity
verbosity' = if Options -> Bool
verbosity Options
args then Verbosity
Logger.Debug else Verbosity
Logger.Message
check :: Check
check =
if Command -> Bool
internal_links Command
args' then Check
Check.InternalLinks else Check
Check.All
Logger
logger <- Verbosity -> IO Logger
Logger.new Verbosity
verbosity'
Command
-> Configuration -> Check -> Logger -> Rules a -> IO ExitCode
forall a.
Command
-> Configuration -> Check -> Logger -> Rules a -> IO ExitCode
invokeCommands Command
args' Configuration
conf Check
check Logger
logger Rules a
rules
defaultParser :: Config.Configuration -> IO Options
defaultParser :: Configuration -> IO Options
defaultParser Configuration
conf =
ParserPrefs -> ParserInfo Options -> IO Options
forall a. ParserPrefs -> ParserInfo a -> IO a
OA.customExecParser ParserPrefs
defaultParserPrefs (Configuration -> ParserInfo Options
defaultParserInfo Configuration
conf)
defaultParserPure :: Config.Configuration -> [String] -> OA.ParserResult Options
defaultParserPure :: Configuration -> [String] -> ParserResult Options
defaultParserPure Configuration
conf =
ParserPrefs
-> ParserInfo Options -> [String] -> ParserResult Options
forall a. ParserPrefs -> ParserInfo a -> [String] -> ParserResult a
OA.execParserPure ParserPrefs
defaultParserPrefs (Configuration -> ParserInfo Options
defaultParserInfo Configuration
conf)
defaultParserPrefs :: OA.ParserPrefs
defaultParserPrefs :: ParserPrefs
defaultParserPrefs = PrefsMod -> ParserPrefs
OA.prefs PrefsMod
OA.showHelpOnError
defaultParserInfo :: Config.Configuration -> OA.ParserInfo Options
defaultParserInfo :: Configuration -> ParserInfo Options
defaultParserInfo Configuration
conf =
Parser Options -> InfoMod Options -> ParserInfo Options
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info (Parser (Options -> Options)
forall a. Parser (a -> a)
OA.helper Parser (Options -> Options) -> Parser Options -> Parser Options
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Configuration -> Parser Options
optionParser Configuration
conf) (InfoMod Options
forall a. InfoMod a
OA.fullDesc InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Options
forall a. String -> InfoMod a
OA.progDesc (
String
progName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" - Static site compiler created with Hakyll"))
invokeCommands :: Command -> Config.Configuration ->
Check.Check -> Logger.Logger -> Rules a -> IO ExitCode
invokeCommands :: Command
-> Configuration -> Check -> Logger -> Rules a -> IO ExitCode
invokeCommands Command
args Configuration
conf Check
check Logger
logger Rules a
rules =
case Command
args of
Command
Build -> Configuration -> Logger -> Rules a -> IO ExitCode
forall a. Configuration -> Logger -> Rules a -> IO ExitCode
Commands.build Configuration
conf Logger
logger Rules a
rules
Check Bool
_ -> Configuration -> Logger -> Check -> IO ExitCode
Commands.check Configuration
conf Logger
logger Check
check
Command
Clean -> Configuration -> Logger -> IO ()
Commands.clean Configuration
conf Logger
logger IO () -> IO ExitCode -> IO ExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ExitCode
ok
Command
Deploy -> Configuration -> IO ExitCode
Commands.deploy Configuration
conf
Preview Int
p -> Configuration -> Logger -> Rules a -> Int -> IO ()
forall a. Configuration -> Logger -> Rules a -> Int -> IO ()
Commands.preview Configuration
conf Logger
logger Rules a
rules Int
p IO () -> IO ExitCode -> IO ExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ExitCode
ok
Command
Rebuild -> Configuration -> Logger -> Rules a -> IO ExitCode
forall a. Configuration -> Logger -> Rules a -> IO ExitCode
Commands.rebuild Configuration
conf Logger
logger Rules a
rules
Server String
_ Int
_ -> Configuration -> Logger -> String -> Int -> IO ()
Commands.server Configuration
conf Logger
logger (Command -> String
host Command
args) (Command -> Int
port Command
args) IO () -> IO ExitCode -> IO ExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ExitCode
ok
Watch String
_ Int
p Bool
s -> Configuration
-> Logger -> String -> Int -> Bool -> Rules a -> IO ()
forall a.
Configuration
-> Logger -> String -> Int -> Bool -> Rules a -> IO ()
Commands.watch Configuration
conf Logger
logger (Command -> String
host Command
args) Int
p (Bool -> Bool
not Bool
s) Rules a
rules IO () -> IO ExitCode -> IO ExitCode
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ExitCode
ok
where
ok :: IO ExitCode
ok = ExitCode -> IO ExitCode
forall (m :: * -> *) a. Monad m => a -> m a
return ExitCode
ExitSuccess
data Options = Options {Options -> Bool
verbosity :: Bool, Options -> Command
optCommand :: Command}
deriving (Int -> Options -> String -> String
[Options] -> String -> String
Options -> String
(Int -> Options -> String -> String)
-> (Options -> String)
-> ([Options] -> String -> String)
-> Show Options
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Options] -> String -> String
$cshowList :: [Options] -> String -> String
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> String -> String
$cshowsPrec :: Int -> Options -> String -> String
Show)
data Command
= Build
| Check {Command -> Bool
internal_links :: Bool}
| Clean
| Deploy
| Preview {Command -> Int
port :: Int}
| Rebuild
| Server {Command -> String
host :: String, port :: Int}
| Watch {host :: String, port :: Int, Command -> Bool
no_server :: Bool }
deriving (Int -> Command -> String -> String
[Command] -> String -> String
Command -> String
(Int -> Command -> String -> String)
-> (Command -> String)
-> ([Command] -> String -> String)
-> Show Command
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Command] -> String -> String
$cshowList :: [Command] -> String -> String
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> String -> String
$cshowsPrec :: Int -> Command -> String -> String
Show)
{-# DEPRECATED Preview "Use Watch instead." #-}
optionParser :: Config.Configuration -> OA.Parser Options
optionParser :: Configuration -> Parser Options
optionParser Configuration
conf = Bool -> Command -> Options
Options (Bool -> Command -> Options)
-> Parser Bool -> Parser (Command -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
verboseParser Parser (Command -> Options) -> Parser Command -> Parser Options
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Configuration -> Parser Command
commandParser Configuration
conf
where
verboseParser :: Parser Bool
verboseParser = Mod FlagFields Bool -> Parser Bool
OA.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"verbose" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'v' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Run in verbose mode")
commandParser :: Config.Configuration -> OA.Parser Command
commandParser :: Configuration -> Parser Command
commandParser Configuration
conf = Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
OA.subparser (Mod CommandFields Command -> Parser Command)
-> Mod CommandFields Command -> Parser Command
forall a b. (a -> b) -> a -> b
$ ((String, Parser Command, InfoMod Command)
-> Mod CommandFields Command -> Mod CommandFields Command)
-> Mod CommandFields Command
-> [(String, Parser Command, InfoMod Command)]
-> Mod CommandFields Command
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
(<>) (Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command)
-> ((String, Parser Command, InfoMod Command)
-> Mod CommandFields Command)
-> (String, Parser Command, InfoMod Command)
-> Mod CommandFields Command
-> Mod CommandFields Command
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Parser Command, InfoMod Command)
-> Mod CommandFields Command
forall a. (String, Parser a, InfoMod a) -> Mod CommandFields a
produceCommand) Mod CommandFields Command
forall a. Monoid a => a
mempty [(String, Parser Command, InfoMod Command)]
forall a. [(String, Parser Command, InfoMod a)]
commands
where
portParser :: Parser Int
portParser = ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option ReadM Int
forall a. Read a => ReadM a
OA.auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"port" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Port to listen on" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OA.value (Configuration -> Int
Config.previewPort Configuration
conf))
hostParser :: Parser String
hostParser = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OA.strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"host" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Host to bind on" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OA.value (Configuration -> String
Config.previewHost Configuration
conf))
produceCommand :: (String, Parser a, InfoMod a) -> Mod CommandFields a
produceCommand (String
c,Parser a
a,InfoMod a
b) = String -> ParserInfo a -> Mod CommandFields a
forall a. String -> ParserInfo a -> Mod CommandFields a
OA.command String
c (Parser a -> InfoMod a -> ParserInfo a
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info (Parser (a -> a)
forall a. Parser (a -> a)
OA.helper Parser (a -> a) -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser a
a) (InfoMod a
b))
commands :: [(String, Parser Command, InfoMod a)]
commands =
[ ( String
"build"
, Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
Build
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Generate the site"
)
, ( String
"check"
, (Bool -> Command) -> Parser (Bool -> Command)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool -> Command
Check Parser (Bool -> Command) -> Parser Bool -> Parser Command
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
OA.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"internal-links" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Check internal links only")
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Validate the site output"
)
, ( String
"clean"
, Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
Clean
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Clean up and remove cache"
)
, ( String
"deploy"
, Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
Deploy
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Upload/deploy your site"
)
, ( String
"preview"
, (Int -> Command) -> Parser (Int -> Command)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int -> Command
Preview Parser (Int -> Command) -> Parser Int -> Parser Command
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
portParser
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"[DEPRECATED] Please use the watch command"
)
, ( String
"rebuild"
, Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
Rebuild
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Clean and build again"
)
, ( String
"server"
, (String -> Int -> Command) -> Parser (String -> Int -> Command)
forall (f :: * -> *) a. Applicative f => a -> f a
pure String -> Int -> Command
Server Parser (String -> Int -> Command)
-> Parser String -> Parser (Int -> Command)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String
hostParser Parser (Int -> Command) -> Parser Int -> Parser Command
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
portParser
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Start a preview server"
)
, ( String
"watch"
, (String -> Int -> Bool -> Command)
-> Parser (String -> Int -> Bool -> Command)
forall (f :: * -> *) a. Applicative f => a -> f a
pure String -> Int -> Bool -> Command
Watch Parser (String -> Int -> Bool -> Command)
-> Parser String -> Parser (Int -> Bool -> Command)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String
hostParser Parser (Int -> Bool -> Command)
-> Parser Int -> Parser (Bool -> Command)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
portParser Parser (Bool -> Command) -> Parser Bool -> Parser Command
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
OA.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"no-server" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Disable the built-in web server")
, InfoMod a
forall a. InfoMod a
OA.fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
OA.progDesc String
"Autocompile on changes and start a preview server. You can watch and recompile without running a server with --no-server."
)
]
progName :: String
progName :: String
progName = IO String -> String
forall a. IO a -> a
unsafePerformIO IO String
getProgName
{-# NOINLINE progName #-}