2016-02-21 13:21:41 +03:00
|
|
|
#!/usr/bin/env stack
|
2016-04-06 01:23:20 +03:00
|
|
|
{- stack runghc --verbosity info
|
2016-04-05 16:59:52 +03:00
|
|
|
--package base-prelude
|
|
|
|
--package directory
|
|
|
|
--package extra
|
|
|
|
--package here
|
|
|
|
--package safe
|
|
|
|
--package shake
|
|
|
|
--package time
|
2016-04-06 01:23:20 +03:00
|
|
|
--package pandoc
|
2016-04-05 16:59:52 +03:00
|
|
|
-}
|
|
|
|
{-
|
|
|
|
Usage: see below.
|
|
|
|
Shake.hs is a more powerful Makefile, providing a number of commands
|
|
|
|
for performing useful tasks. Compiling this script is suggested, so that
|
|
|
|
it runs quicker and will not be affected eg when exploring old code versions.
|
|
|
|
More about Shake: http://shakebuild.com/manual
|
|
|
|
Requires: https://www.haskell.org/downloads#stack
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-05 16:59:52 +03:00
|
|
|
Shake notes:
|
|
|
|
wishlist:
|
2016-04-07 18:52:41 +03:00
|
|
|
just one shake import
|
2016-04-05 16:59:52 +03:00
|
|
|
wildcards in phony rules
|
|
|
|
multiple individually accessible wildcards
|
2016-04-07 18:52:41 +03:00
|
|
|
not having to write :: Action ExitCode after a non-final cmd
|
2016-04-05 16:59:52 +03:00
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE PackageImports, QuasiQuotes #-}
|
|
|
|
|
|
|
|
import Prelude ()
|
|
|
|
import "base-prelude" BasePrelude
|
|
|
|
-- import "base" System.Console.GetOpt
|
|
|
|
import "extra" Data.List.Extra
|
|
|
|
import "here" Data.String.Here
|
|
|
|
import "safe" Safe
|
|
|
|
import "shake" Development.Shake
|
|
|
|
import "shake" Development.Shake.FilePath
|
|
|
|
import "time" Data.Time
|
|
|
|
import "directory" System.Directory as S (getDirectoryContents)
|
|
|
|
|
|
|
|
usage = [i|Usage:
|
2016-04-06 01:56:14 +03:00
|
|
|
./Shake.hs compile # compile this script (optional)
|
|
|
|
./Shake --help # show options, eg --color
|
2016-04-06 02:07:37 +03:00
|
|
|
./Shake # show commands
|
2016-04-07 18:52:41 +03:00
|
|
|
./Shake site # generate things needed for the website
|
2016-04-06 01:56:14 +03:00
|
|
|
./Shake manpages # generate nroff files for man
|
|
|
|
./Shake webmanpages # generate web man pages for hakyll
|
2016-04-07 18:52:41 +03:00
|
|
|
./Shake webmanual # generate combined web man page for hakyll
|
2016-04-05 16:59:52 +03:00
|
|
|
|]
|
2016-02-21 13:21:41 +03:00
|
|
|
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
pandoc =
|
|
|
|
-- "stack exec -- pandoc" -- use the pandoc required above
|
|
|
|
"pandoc" -- use pandoc in PATH (faster)
|
2016-04-10 00:24:33 +03:00
|
|
|
hakyllstd = "site/hakyll-std/hakyll-std"
|
2016-02-21 13:21:41 +03:00
|
|
|
|
|
|
|
main = do
|
|
|
|
|
|
|
|
pandocFilters <-
|
2016-04-06 01:46:44 +03:00
|
|
|
map ("doc" </>). nub . sort . map (-<.> "") . filter ("pandoc-" `isPrefixOf`)
|
|
|
|
<$> S.getDirectoryContents "doc"
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-05 16:59:52 +03:00
|
|
|
shakeArgs
|
|
|
|
shakeOptions{
|
2016-04-13 06:32:01 +03:00
|
|
|
shakeVerbosity=Loud
|
2016-04-05 16:59:52 +03:00
|
|
|
-- ,shakeReport=[".shake.html"]
|
|
|
|
} $ do
|
|
|
|
|
|
|
|
want ["help"]
|
|
|
|
|
|
|
|
phony "help" $ liftIO $ putStrLn usage
|
|
|
|
|
|
|
|
phony "compile" $ need ["Shake"]
|
|
|
|
"Shake" %> \out -> do
|
|
|
|
need ["Shake.hs"]
|
|
|
|
cmd "stack ghc Shake.hs" :: Action ExitCode
|
|
|
|
putLoud "Compiled ./Shake, you can now use this instead of ./Shake.hs"
|
|
|
|
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
-- docs
|
|
|
|
|
2016-04-10 22:11:19 +03:00
|
|
|
phony "docs" $ do
|
2016-04-10 00:24:33 +03:00
|
|
|
need [
|
|
|
|
"manpages"
|
2016-04-10 22:11:19 +03:00
|
|
|
]
|
|
|
|
|
2016-04-13 06:23:53 +03:00
|
|
|
let webmanual = "site/manual.md"
|
|
|
|
|
2016-04-10 22:11:19 +03:00
|
|
|
phony "site" $ do
|
|
|
|
need [
|
|
|
|
"webmanpages"
|
2016-04-13 06:23:53 +03:00
|
|
|
,webmanual
|
2016-04-10 00:24:33 +03:00
|
|
|
,hakyllstd
|
|
|
|
]
|
|
|
|
cmd Shell (Cwd "site") "hakyll-std/hakyll-std" "build"
|
|
|
|
|
|
|
|
hakyllstd %> \out -> do
|
|
|
|
let dir = takeDirectory out
|
|
|
|
need [out <.> "hs", dir </> "TableOfContents.hs"]
|
|
|
|
cmd (Cwd dir) "stack ghc hakyll-std"
|
2016-04-06 02:16:38 +03:00
|
|
|
|
2016-04-07 18:52:41 +03:00
|
|
|
-- man pages
|
2016-04-08 17:01:11 +03:00
|
|
|
|
|
|
|
let
|
|
|
|
manpageNames = [ -- in suggested reading order
|
|
|
|
"hledger.1"
|
|
|
|
,"hledger-ui.1"
|
|
|
|
,"hledger-web.1"
|
|
|
|
,"hledger-api.1"
|
|
|
|
,"hledger_journal.5"
|
|
|
|
,"hledger_csv.5"
|
|
|
|
,"hledger_timelog.5"
|
|
|
|
,"hledger_timedot.5"
|
|
|
|
]
|
|
|
|
|
|
|
|
-- hledger.1 -> hledger, hledger_journal.5 -> journal
|
|
|
|
manpageNameToUri m | "hledger_" `isPrefixOf` m = dropExtension $ drop 8 m
|
|
|
|
| otherwise = dropExtension m
|
|
|
|
|
|
|
|
-- hledger -> hledger.1, journal -> hledger_journal.5
|
|
|
|
manpageUriToName u | "hledger" `isPrefixOf` u = u <.> "1"
|
|
|
|
| otherwise = "hledger_" ++ u <.> "5"
|
|
|
|
|
|
|
|
-- hledger.1 -> hledger/doc, hledger_journal.5 -> hledger-lib/doc
|
|
|
|
manpageDir m
|
|
|
|
| '_' `elem` m = "hledger-lib" </> "doc"
|
|
|
|
| otherwise = dropExtension m </> "doc"
|
|
|
|
|
2016-04-09 23:19:31 +03:00
|
|
|
-- some man pages have their md source assembled from parts with m4
|
|
|
|
let m4manpages = [manpageDir m </> m <.> ".md" | m <- ["hledger.1"]] -- hledger/doc/hledger.1.md
|
|
|
|
m4manpages |%> \out -> do -- hledger/doc/hledger.1.md
|
|
|
|
let dir = takeDirectory out -- hledger/doc
|
|
|
|
m4src = out -<.> "m4" <.> "md" -- hledger/doc/hledger.1.m4.md
|
|
|
|
m4lib = "doc/lib.m4"
|
|
|
|
-- assume all other m4 files in dir are included by this one
|
|
|
|
m4deps <- liftIO $ filter (/= m4src) . filter (".m4.md" `isSuffixOf`) . map (dir </>)
|
|
|
|
<$> S.getDirectoryContents dir
|
|
|
|
need $ m4src : m4lib : m4deps
|
|
|
|
cmd Shell "m4 -P -DWEB -DMAN -I" dir m4lib m4src ">" out
|
2016-04-07 18:52:41 +03:00
|
|
|
|
2016-04-09 23:19:31 +03:00
|
|
|
-- compile pandoc filters, used eg for adjusting manpage md source for web or man output
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
phony "pandocfilters" $ need pandocFilters
|
|
|
|
pandocFilters |%> \out -> do
|
|
|
|
need [out <.> "hs"]
|
|
|
|
cmd ("stack ghc") out
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-09 23:19:31 +03:00
|
|
|
-- adjust man page mds for man output and convert to nroff, with pandoc
|
2016-04-08 17:01:11 +03:00
|
|
|
let manpages = [manpageDir m </> m | m <- manpageNames] -- hledger/doc/hledger.1, hledger-lib/doc/hledger_journal.5
|
|
|
|
phony "manpages" $ need manpages
|
|
|
|
manpages |%> \out -> do
|
|
|
|
let md = out <.> "md" -- hledger/doc/hledger.1.md
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
tmpl = "doc/manpage.nroff"
|
2016-02-21 13:21:41 +03:00
|
|
|
need $ md : tmpl : pandocFilters
|
2016-04-08 07:58:42 +03:00
|
|
|
cmd pandoc md "-s --template" tmpl
|
2016-04-06 18:20:27 +03:00
|
|
|
"--filter doc/pandoc-drop-web-blocks"
|
2016-04-06 01:46:44 +03:00
|
|
|
"--filter doc/pandoc-drop-html-blocks"
|
|
|
|
"--filter doc/pandoc-drop-html-inlines"
|
|
|
|
"--filter doc/pandoc-drop-links"
|
|
|
|
"--filter doc/pandoc-drop-notes"
|
2016-04-08 07:58:42 +03:00
|
|
|
"-o" out
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-09 23:19:31 +03:00
|
|
|
-- adjust man page mds for (hakyll) web output, with pandoc
|
2016-04-08 17:01:11 +03:00
|
|
|
let webmanpages = ["site" </> manpageNameToUri m <.>".md" | m <- manpageNames] -- site/hledger.md, site/journal.md
|
|
|
|
phony "webmanpages" $ need webmanpages
|
|
|
|
webmanpages |%> \out -> do
|
|
|
|
let m = manpageUriToName $ dropExtension $ takeFileName out -- hledger.1
|
|
|
|
md = manpageDir m </> m <.> "md" -- hledger/doc/hledger.1.md
|
2016-04-09 23:36:48 +03:00
|
|
|
heading = let h = dropExtension m
|
|
|
|
in if "hledger_" `isPrefixOf` h
|
|
|
|
then drop 8 h ++ " format"
|
|
|
|
else h
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
need $ md : pandocFilters
|
2016-04-09 23:36:48 +03:00
|
|
|
liftIO $ writeFile out $ "# " ++ heading ++ "\n\n"
|
|
|
|
cmd Shell pandoc md "-t markdown --atx-headers"
|
2016-04-07 18:52:41 +03:00
|
|
|
"--filter doc/pandoc-demote-headers"
|
|
|
|
-- "--filter doc/pandoc-add-toc"
|
|
|
|
-- "--filter doc/pandoc-drop-man-blocks"
|
2016-04-09 23:36:48 +03:00
|
|
|
">>" out
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-09 23:19:31 +03:00
|
|
|
-- adjust and combine man page mds for single-page web output, using pandoc
|
2016-04-07 18:52:41 +03:00
|
|
|
|
|
|
|
phony "webmanual" $ need [ webmanual ]
|
2016-04-13 06:23:53 +03:00
|
|
|
webmanual %> \out -> do
|
2016-04-08 17:01:11 +03:00
|
|
|
need webmanpages
|
2016-04-08 07:58:42 +03:00
|
|
|
liftIO $ writeFile webmanual [i|
|
|
|
|
<style>
|
|
|
|
#toc > ol > li {
|
|
|
|
padding-top:1em;
|
|
|
|
font-weight:bold;
|
|
|
|
}
|
|
|
|
#toc > ol > li > ol {
|
|
|
|
font-weight:normal;
|
|
|
|
}
|
|
|
|
</style>
|
|
|
|
* toc
|
|
|
|
|
|
|
|
|]
|
2016-04-08 17:01:11 +03:00
|
|
|
forM_ webmanpages $ \f -> do -- site/hledger.md, site/journal.md
|
2016-04-09 23:36:48 +03:00
|
|
|
-- let heading =
|
|
|
|
-- let h = dropExtension $ takeFileName f -- hledger, journal
|
|
|
|
-- in if "hledger" `isPrefixOf` h
|
|
|
|
-- then h -- hledger
|
|
|
|
-- else h ++ " format" -- journal format
|
|
|
|
-- cmd Shell ("printf '\\n## "++ heading ++"\\n\\n' >>") webmanual :: Action ExitCode
|
|
|
|
cmd Shell ("printf '\\n\\n' >>") webmanual :: Action ExitCode
|
2016-04-09 04:14:49 +03:00
|
|
|
cmd Shell "pandoc" f "-t markdown --atx-headers"
|
2016-04-09 23:36:48 +03:00
|
|
|
-- "--filter doc/pandoc-drop-man-blocks"
|
2016-04-07 18:52:41 +03:00
|
|
|
"--filter doc/pandoc-drop-toc"
|
2016-04-08 07:58:42 +03:00
|
|
|
-- "--filter doc/pandoc-capitalize-headers"
|
2016-04-07 18:52:41 +03:00
|
|
|
"--filter doc/pandoc-demote-headers"
|
|
|
|
">>" webmanual :: Action ExitCode
|
2016-02-21 13:21:41 +03:00
|
|
|
|
2016-04-06 01:40:59 +03:00
|
|
|
-- cleanup
|
|
|
|
|
2016-02-21 13:21:41 +03:00
|
|
|
phony "clean" $ do
|
|
|
|
putNormal "Cleaning generated files"
|
2016-04-09 23:19:31 +03:00
|
|
|
removeFilesAfter "." ["hledger/doc/hledger.1.md"]
|
2016-04-08 17:01:11 +03:00
|
|
|
removeFilesAfter "." webmanpages
|
2016-04-07 18:52:41 +03:00
|
|
|
removeFilesAfter "." [webmanual]
|
doc: experimental m4-based man page build process
The new m4manpages, m4webmanpages targets generate nroff and markdown
man pages via an alternate, excitingly complicated process, involving
shake, hakyll, pandoc *and* m4. Currently just the hledger man page is
processed this way, and the output (hledger/doc/m4-hledger.1,
site/m4-hledger.1.md) is equivalent to that of the non-m4 process.
Pro: selecting and massaging web/man content may be smoother with m4
than with pandoc filters. File inclusion allows documentation to be
broken up into chunks, which may be easier to edit, reorganize and
reuse. Macros could reduce boilerplate and enable more featureful and
attractive docs.
Con: the non-m4 process was simpler, easier to for contributors to
understand and working well enough. YAGNI.
2016-04-06 18:23:12 +03:00
|
|
|
|
|
|
|
phony "Clean" $ do
|
|
|
|
need ["clean"]
|
2016-04-08 17:01:11 +03:00
|
|
|
putNormal "Cleaning generated man page nroffs"
|
|
|
|
removeFilesAfter "." manpages
|
2016-04-10 00:24:33 +03:00
|
|
|
putNormal "Cleaning all hakyll generated files"
|
|
|
|
removeFilesAfter "site" ["_*"]
|
|
|
|
putNormal "Cleaning executables"
|
|
|
|
removeFilesAfter "." $ hakyllstd : pandocFilters
|
2016-02-21 13:21:41 +03:00
|
|
|
putNormal "Cleaning object files"
|
2016-04-10 00:24:33 +03:00
|
|
|
removeFilesAfter "doc" ["*.o","*.p_o","*.hi"] -- forces rebuild of exes ?
|
|
|
|
removeFilesAfter "site" ["*.o","*.p_o","*.hi"]
|
2016-02-21 13:21:41 +03:00
|
|
|
putNormal "Cleaning shake build files"
|
2016-04-13 06:32:01 +03:00
|
|
|
removeFilesAfter ".shake" ["//*"]
|