summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Hakyll/Commands.hs51
-rw-r--r--src/Hakyll/Main.hs27
2 files changed, 63 insertions, 15 deletions
diff --git a/src/Hakyll/Commands.hs b/src/Hakyll/Commands.hs
index d86fd5c..7951f4e 100644
--- a/src/Hakyll/Commands.hs
+++ b/src/Hakyll/Commands.hs
@@ -1,4 +1,4 @@
---------------------------------------------------------------------------------
+ --------------------------------------------------------------------------------
-- | Implementation of Hakyll commands: build, preview...
{-# LANGUAGE CPP #-}
module Hakyll.Commands
@@ -9,12 +9,14 @@ module Hakyll.Commands
, rebuild
, server
, deploy
+ , watch
) where
--------------------------------------------------------------------------------
import System.Exit (exitWith, ExitCode)
import Control.Applicative
+import Control.Concurrent
--------------------------------------------------------------------------------
import qualified Hakyll.Check as Check
@@ -26,8 +28,11 @@ import Hakyll.Core.Runtime
import Hakyll.Core.Util.File
--------------------------------------------------------------------------------
+#ifdef WATCH_SERVER
+import Hakyll.Preview.Poll (watchUpdates)
+#endif
+
#ifdef PREVIEW_SERVER
-import Hakyll.Preview.Poll
import Hakyll.Preview.Server
#endif
@@ -60,18 +65,39 @@ clean conf = do
-- | Preview the site
preview :: Configuration -> Verbosity -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
-preview conf verbosity rules port = do
+preview conf verbosity rules port = do
+ deprecatedMessage
+ watch conf verbosity port True rules
+ where
+ deprecatedMessage = mapM_ putStrLn [ "The preview command has been deprecated."
+ , "Use the watch command for recompilation and serving."
+ ]
+#else
+preview _ _ _ _ = previewServerDisabled
+#endif
+
+
+--------------------------------------------------------------------------------
+-- | Watch and recompile for changes
+
+watch :: Configuration -> Verbosity -> Int -> Bool -> Rules a -> IO ()
+#ifdef WATCH_SERVER
+watch conf verbosity port runServer rules = do
watchUpdates conf update
- server conf port
+ _ <- forkIO (server')
+ loop
where
update = do
(_, ruleSet) <- run conf verbosity rules
return $ rulesPattern ruleSet
+
+ loop = threadDelay 100000 >> loop
+
+ server' = if runServer then server conf port else return ()
#else
-preview _ _ _ _ = previewServerDisabled
+watch _ _ _ _ _ = watchServerDisabled
#endif
-
--------------------------------------------------------------------------------
-- | Rebuild the site
rebuild :: Configuration -> Verbosity -> Rules a -> IO ExitCode
@@ -111,3 +137,16 @@ previewServerDisabled =
, "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
+
diff --git a/src/Hakyll/Main.hs b/src/Hakyll/Main.hs
index 7e50418..4b30939 100644
--- a/src/Hakyll/Main.hs
+++ b/src/Hakyll/Main.hs
@@ -41,14 +41,15 @@ hakyllWith conf rules = do
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
- Server _ _ -> Commands.server conf (port args')
+ 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
+ Server _ _ -> Commands.server conf (port args')
+ Watch _ p s -> Commands.watch conf verbosity' p (not s) rules
--------------------------------------------------------------------------------
@@ -67,6 +68,7 @@ data HakyllArgs
| Preview {verbose :: Bool, port :: Int}
| Rebuild {verbose :: Bool}
| Server {verbose :: Bool, port :: Int}
+ | Watch {verbose :: Bool, port :: Int, no_server :: Bool }
deriving (Data, Typeable, Show)
@@ -80,10 +82,12 @@ hakyllArgs = modes
, (Deploy $ verboseFlag def) &= help "Upload/deploy your site"
, (Help $ verboseFlag def) &= help "Show this message" &= auto
, (Preview (verboseFlag def) (portFlag 8000)) &=
- help "Start a preview server and autocompile on changes"
+ help "[Deprecated] Please use the watch command"
, (Rebuild $ verboseFlag def) &= help "Clean and build again"
, (Server (verboseFlag def) (portFlag 8000)) &=
help "Start a preview server"
+ , (Watch (verboseFlag def) (portFlag 8000) (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
@@ -94,6 +98,11 @@ verboseFlag x = x &= help "Run in verbose mode"
--------------------------------------------------------------------------------
+noServerFlag :: Data a => a -> a
+noServerFlag x = x &= help "Disable the built-in web server"
+{-# INLINE noServerFlag #-}
+
+--------------------------------------------------------------------------------
portFlag :: Data a => a -> a
portFlag x = x &= help "Port to listen on"
{-# INLINE portFlag #-}