{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Rib.App
( Command (..),
commandParser,
run,
runWith,
)
where
import Control.Concurrent (threadDelay)
import Control.Concurrent.Async (race_)
import Control.Exception.Safe (catch)
import Development.Shake hiding (command)
import Development.Shake.Forward (shakeForward)
import Options.Applicative
import Path
import Path.IO
import Relude
import qualified Rib.Server as Server
import Rib.Settings (RibSettings (..))
import Rib.Watch (onTreeChange)
import System.FSNotify (Event (..), eventIsDirectory, eventPath)
import System.IO (BufferMode (LineBuffering), hSetBuffering)
data Command
=
OneOff
|
Generate
{
full :: Bool
}
|
Watch
|
Serve
{
port :: Int,
dontWatch :: Bool
}
deriving (Show, Eq, Generic)
commandParser :: Parser Command
commandParser =
hsubparser $
mconcat
[ command "generate" $ info generateCommand $ progDesc "Run one-off generation of static files",
command "watch" $ info watchCommand $ progDesc "Watch the source directory, and generate when it changes",
command "serve" $ info serveCommand $ progDesc "Like watch, but also starts a HTTP server"
]
where
generateCommand =
Generate <$> switch (long "full" <> help "Do a full generation (toggles shakeRebuild)")
watchCommand =
pure Watch
serveCommand =
Serve
<$> option auto (long "port" <> short 'p' <> help "HTTP server port" <> showDefault <> value 8080 <> metavar "PORT")
<*> switch (long "no-watch" <> help "Serve only; don't watch and regenerate")
run ::
Path Rel Dir ->
Path Rel Dir ->
Action () ->
IO ()
run src dst buildAction = runWith src dst buildAction =<< execParser opts
where
opts =
info
(commandParser <**> helper)
( fullDesc
<> progDesc "Rib static site generator CLI"
)
runWith :: Path Rel Dir -> Path Rel Dir -> Action () -> Command -> IO ()
runWith src dst buildAction ribCmd = do
when (src == currentRelDir) $
fail "cannot use '.' as source directory."
flip hSetBuffering LineBuffering `mapM_` [stdout, stderr]
let ribSettings =
case ribCmd of
OneOff ->
RibSettings src dst Silent False
Generate fullGen ->
RibSettings src dst Verbose fullGen
_ ->
RibSettings src dst Verbose False
case ribCmd of
OneOff ->
runShake ribSettings buildAction
Generate _ ->
runShakeBuild ribSettings
Watch ->
runShakeAndObserve ribSettings
Serve p dw -> do
race_ (Server.serve p $ toFilePath dst) $ do
if dw
then threadDelay maxBound
else runShakeAndObserve ribSettings
where
currentRelDir = [reldir|.|]
shakeDatabaseDir :: Path Rel Dir = src </> [reldir|.shake|]
runShakeAndObserve ribSettings = do
runShakeBuild $ ribSettings {_ribSettings_fullGen = True}
putStrLn $ "[Rib] Watching " <> toFilePath src <> " for changes"
onSrcChange $ runShakeBuild ribSettings
runShakeBuild ribSettings = do
runShake ribSettings $ do
putInfo $ "[Rib] Generating " <> toFilePath src <> " (full=" <> show (_ribSettings_fullGen ribSettings) <> ")"
buildAction
runShake ribSettings shakeAction = do
shakeForward (shakeOptionsFrom ribSettings) shakeAction
`catch` handleShakeException
handleShakeException (e :: ShakeException) =
putStrLn $
"[Rib] Unhandled exception when building " <> shakeExceptionTarget e <> ": " <> show e
shakeOptionsFrom settings =
shakeOptions
{ shakeVerbosity = _ribSettings_verbosity settings,
shakeFiles = toFilePath shakeDatabaseDir,
shakeRebuild = bool [] [(RebuildNow, "**")] (_ribSettings_fullGen settings),
shakeLintInside = [""],
shakeExtra = addShakeExtra settings (shakeExtra shakeOptions)
}
onSrcChange f = do
workDir <- getCurrentDir
dirBlacklist <- traverse makeAbsolute [shakeDatabaseDir, src </> [reldir|.git|]]
let isBlacklisted :: FilePath -> Bool
isBlacklisted p = or $ flip fmap dirBlacklist $ \b -> toFilePath b `isPrefixOf` p
onTreeChange src $ \allEvents -> do
let events = filter (not . isBlacklisted . eventPath) allEvents
unless (null events) $ do
logEvent workDir `mapM_` events
f
logEvent workDir e = do
eventRelPath <-
if eventIsDirectory e
then fmap toFilePath . makeRelative workDir =<< parseAbsDir (eventPath e)
else fmap toFilePath . makeRelative workDir =<< parseAbsFile (eventPath e)
putStrLn $ eventLogPrefix e <> " " <> eventRelPath
eventLogPrefix = \case
Added _ _ _ -> "A"
Modified _ _ _ -> "M"
Removed _ _ _ -> "D"
Unknown _ _ _ -> "?"