mkdocs/compile.hs

191 lines
6.6 KiB
Haskell
Raw Normal View History

2016-03-25 10:39:17 +00:00
#!/usr/bin/env stack
-- stack --install-ghc runghc --package turtle --resolver lts-5.5 --verbosity silent --package=ansi-terminal
{-# LANGUAGE OverloadedStrings #-}
2016-03-25 16:40:59 +00:00
import qualified Control.Foldl as Fold
2016-03-25 10:39:17 +00:00
import qualified Data.Text.IO as T
import Filesystem.Path (addExtension, replaceExtension)
import qualified Filesystem.Path as F
import Prelude hiding (FilePath)
import System.Console.ANSI
import Turtle
2016-03-25 20:39:12 +00:00
import Data.Maybe (isJust,fromJust)
2016-03-25 10:39:17 +00:00
2016-03-25 16:40:59 +00:00
-- Command Line Options
data Options =
Options { web :: Bool
, reveal :: Bool
, pdf :: Bool
, beamer :: Bool
, debug :: Bool
, file :: Maybe FilePath
} deriving (Show)
2016-03-25 10:39:17 +00:00
parser :: Parser Options
parser = Options <$> switch "web" 'w' "generate HTML web page"
<*> switch "reveal" 'r' "generate HTML presentation using reveal"
<*> switch "pdf" 'p' "generate PDF article"
<*> switch "beamer" 'b' "generate PDF presentation using beamer"
2016-03-25 16:40:59 +00:00
<*> switch "debug" 'd' "debug mode (show commands)"
2016-03-25 10:39:17 +00:00
<*> optional (argPath "file" "markdown file path")
2016-03-25 16:40:59 +00:00
initOptions :: IO Options
initOptions = do
rawopts <- options "compile files" parser
return $ if web rawopts || reveal rawopts || pdf rawopts || beamer rawopts
then rawopts
else rawopts { web = True
, reveal = True
, pdf = True
, beamer = True }
2016-03-25 10:39:17 +00:00
main :: IO ()
main = do
2016-03-25 16:40:59 +00:00
opts <- initOptions
2016-03-25 17:04:27 +00:00
maindir <- pwd
2016-03-25 10:39:17 +00:00
sh $ do
argfile <- case file opts of
2016-03-25 16:40:59 +00:00
Nothing -> findMarkdownFiles
2016-03-25 10:39:17 +00:00
Just someFile -> return someFile
liftIO $ do
2016-03-25 20:39:12 +00:00
yellowPrn ("-- " <> format fp argfile <> " --")
2016-03-25 10:39:17 +00:00
cd (directory argfile)
2016-03-25 16:40:59 +00:00
when (web opts) (toWeb (debug opts) argfile)
when (reveal opts) (toReveal (debug opts) argfile)
when (pdf opts) (toPdf (debug opts) argfile)
when (beamer opts) (toBeamer (debug opts) argfile)
2016-03-25 17:04:27 +00:00
cd maindir
2016-03-25 16:40:59 +00:00
-- | Find Markdown Files (skip hidden directories)
findMarkdownFiles :: Shell FilePath
2016-03-25 20:39:12 +00:00
findMarkdownFiles = do
fic <- find (has ".md") "." & fgrep (invert (prefix "./."))
let mf = stripPrefix "./" fic
_ <- guard (isJust mf)
return (fromJust mf)
2016-03-25 16:40:59 +00:00
-- | basic exec command with debug option and colors DONE or FAILED status
execcmd :: Bool -> FilePath -> Text -> IO ()
execcmd dbg dest cmd = do
when dbg (T.putStrLn cmd)
T.putStr $ format fp dest <> " "
answer <- shell cmd empty
case answer of
ExitSuccess -> greenPrn "[DONE]"
ExitFailure _ -> redPrn "[FAILED]"
2016-03-25 17:04:27 +00:00
toprefix :: FilePath -> FilePath
2016-03-25 20:39:12 +00:00
toprefix fpath = F.concat $ map (const "..") (filter (/= "./") (splitDirectories (directory fpath)))
2016-03-25 17:04:27 +00:00
2016-03-25 16:40:59 +00:00
-- | Generate HTML format
toWeb :: Bool -> FilePath -> IO ()
toWeb dbg fpath = do
let dest = filename (replaceExtension fpath "html")
2016-03-25 17:04:27 +00:00
pr = toprefix fpath
2016-03-25 16:40:59 +00:00
cmd = "pandoc -s -S --toc -mathjax -t html5 --smart "
<> "--css " <> format fp (pr </> "styling.css") <> " "
<> "-A " <> format fp (pr </> "footer.html") <> " "
<> "-o " <> format fp dest <> " "
<> format fp (filename fpath)
execcmd dbg dest cmd
-- | Generate HTML Reveal.js Presentation
toReveal :: Bool -> FilePath -> IO ()
toReveal dbg fpath = do
2016-03-25 20:47:13 +00:00
mslideLevel <- fold (fpath & filename
& input
& grep (prefix "slide_level: ")
& sed (prefix "slide_level: " *> star digit))
Fold.head
let slideLevel = maybe "2" (\l -> if l == "" then "2" else l) mslideLevel
dest = fpath & filename
2016-03-25 20:39:12 +00:00
& dropExtension
& flip addExtension "reveal"
& flip addExtension "html"
2016-03-25 10:39:17 +00:00
pr :: FilePath
2016-03-25 17:04:27 +00:00
pr = toprefix fpath
2016-03-25 10:39:17 +00:00
template = pr </> "template-revealjs.html"
prt :: Text
prt = format fp pr
cmd = "pandoc -s -mathjax -t html5 "
<> "--template=" <> format fp template <> " "
<> "--section-divs "
2016-03-25 20:47:13 +00:00
<> "--slide-level=" <> slideLevel <> " "
2016-03-25 10:39:17 +00:00
<> "--variable transition=linear "
<> "--variable prefix=" <> prt <> " "
<> "-o " <> format fp dest <> " "
<> format fp (filename fpath)
2016-03-25 16:40:59 +00:00
execcmd dbg dest cmd
2016-03-25 10:39:17 +00:00
2016-03-25 16:40:59 +00:00
-- | Generate PDF Document using XeLaTeX
toPdf :: Bool -> FilePath -> IO ()
toPdf dbg fpath = do
2016-03-25 20:39:12 +00:00
let dest = fpath & filename
& dropExtension
& flip addExtension "pdf"
2016-03-25 17:04:27 +00:00
pr = toprefix fpath
2016-03-25 16:40:59 +00:00
template = pr </> "template.latex"
cmd = "pandoc -s -S -N --toc "
<> "--template=" <> format fp template <> " "
<> "--section-divs "
<> "--variable fontsize=14pt "
<> "--variable linkcolor=orange "
<> "--variable urlcolor=orange "
<> "--latex-engine=xelatex "
<> "-o " <> format fp dest <> " "
<> format fp (filename fpath)
execcmd dbg dest cmd
2016-03-25 10:39:17 +00:00
2016-03-25 16:40:59 +00:00
-- | Generate Beamer Presentation PDF
toBeamer :: Bool -> FilePath -> IO ()
toBeamer dbg fpath = do
2016-03-25 20:39:12 +00:00
mslideLevel <- fold (fpath & filename
& input
& grep (prefix "slide_level: ")
& sed (prefix "slide_level: " *> star digit))
2016-03-25 16:40:59 +00:00
Fold.head
let slideLevel = maybe "2" (\l -> if l == "" then "2" else l) mslideLevel
2016-03-25 20:39:12 +00:00
dest = fpath & filename
& dropExtension
& flip addExtension "beamer"
& flip addExtension "pdf"
2016-03-25 16:40:59 +00:00
cmd :: Text
cmd = "pandoc -s -S -N "
<> "-t beamer "
<> "--slide-level=" <> slideLevel <> " "
<> "--variable fontsize=14pt "
<> "--variable linkcolor=orange "
<> "--variable urlcolor=orange "
<> "--latex-engine=xelatex "
<> "-o " <> format fp dest <> " "
<> format fp (filename fpath)
execcmd dbg dest cmd
2016-03-25 10:39:17 +00:00
2016-03-25 16:40:59 +00:00
-- # Colors Helpers (should be a sub lib)
-- import System.Console.ANSI
prnColor :: Color -> Text -> IO ()
prnColor c txt = do
setSGR [SetColor Foreground Dull c]
2016-03-25 10:39:17 +00:00
T.putStrLn txt
setSGR [Reset]
2016-03-25 16:40:59 +00:00
greenPrn :: Text -> IO ()
greenPrn = prnColor Green
2016-03-25 10:39:17 +00:00
redPrn :: Text -> IO ()
2016-03-25 16:40:59 +00:00
redPrn = prnColor Red
yellowPrn :: Text -> IO ()
yellowPrn = prnColor Yellow
-- # Grep Files helper
-- | Same as grep put to be used after find or ls
fgrep :: Pattern a -> Shell FilePath -> Shell FilePath
fgrep pat sp = do
fpath <- sp
_:_ <- return (match pat (either id id (toText fpath)))
return fpath