xmonad/util/GenerateManpage.hs
Peter Simons 886a0d4041 GenerateManpage: greatly simplify the code
We can take advantage of modern Pandoc features to move information like the
release date, the man page section, etc. into the markdown source rather than
having to insert that data during the rendering process. The only thing that
remains to be figured out by this tool is the set of known key bindings.
2018-08-20 11:35:31 +02:00

89 lines
3.1 KiB
Haskell

{-# LANGUAGE FlexibleContexts #-}
-- Generates a in-memory version of "man/xmonad.1.markdown" that has the list
-- of known key-bindings is inserted automatically from "Config.hs". That
-- document is then rendered with Pandoc as "man/xmonad.1" and
-- "man/xmonad.1.html".
--
-- Unlike the rest of xmonad, this file is released under the GNU General
-- Public License version 2 or later.
import Control.Monad
import Control.Monad.IO.Class (liftIO)
import Data.Char
import Data.List
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Text.Pandoc
import Text.Regex.Posix
main :: IO ()
main = do
keybindings <- guessBindings
markdownSource <- readFile "./man/xmonad.1.markdown"
runIOorExplode $ do
parsed <- readMarkdown (def { readerStandalone = True, readerExtensions = pandocExtensions })
. T.pack
. unlines
. replace "___KEYBINDINGS___" keybindings
. lines
$ markdownSource
manTemplate <- getDefaultTemplate "man"
manBody <- writeMan def { writerTemplate = Just manTemplate } parsed
liftIO $ TIO.writeFile "./man/xmonad.1" $ manBody
liftIO $ putStrLn "Documentation created: man/xmonad.1"
htmltemplate <- getDefaultTemplate "html"
htmlBody <- writeHtml5String def
{ writerTemplate = Just htmltemplate
, writerTableOfContents = True }
parsed
liftIO $ TIO.writeFile "./man/xmonad.1.html" htmlBody
liftIO $ putStrLn "Documentation created: man/xmonad.1.html"
-- | The format for the docstrings in "Config.hs" takes the following form:
--
-- @
-- -- mod-x %! Frob the whatsit
-- @
--
-- "Frob the whatsit" will be used as the description for keybinding "mod-x".--
-- If the name of the key binding is omitted, the function tries to guess it
-- from the rest of the line. For example:
--
-- @
-- [ ((modMask .|. shiftMask, xK_Return), spawn "xterm") -- %! Launch an xterm
-- @
--
-- Here, "mod-shift-return" will be used as the key binding name.
guessBindings :: IO String
guessBindings = do
buf <- readFile "./src/XMonad/Config.hs"
return (intercalate "\n\n" (map markdownDefn (allBindings buf)))
allBindings :: String -> [(String, String)]
allBindings xs = map (binding . map trim) (xs =~ "(.*)--(.*)%!(.*)")
binding :: [String] -> (String, String)
binding [ _, bindingLine, "", desc ] = (guessKeys bindingLine, desc)
binding [ _, _, keyCombo, desc ] = (keyCombo, desc)
guessKeys :: String -> String
guessKeys line = concat $ intersperse "-" (modifiers ++ [map toLower key])
where modifiers = map (!!1) (line =~ "(mod|shift|control)Mask")
(_, _, _, [key]) = line =~ "xK_([_[:alnum:]]+)" :: (String, String, String, [String])
-- FIXME: What escaping should we be doing on these strings?
markdownDefn :: (String, String) -> String
markdownDefn (key, desc) = key ++ "\n: " ++ desc
replace :: Eq a => a -> a -> [a] -> [a]
replace x y = map (\a -> if a == x then y else a)
trim :: String -> String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace