summaryrefslogtreecommitdiff
path: root/man/make-pandoc-man-pages.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-06-28 14:39:17 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2015-06-28 14:39:17 -0700
commitfe625e053d078e03d824a1df746196b8a2c697b1 (patch)
tree0129bded228d952594d06a8ed675154d05909abc /man/make-pandoc-man-pages.hs
parent3e5b4faaf2a99950991ff7b16c0e0b06234b9792 (diff)
New method for producing man pages.
This change adds `--man1` and `--man5` options to pandoc, so pandoc can generate its own man pages. It removes the old overly complex method of building a separate executable (but not installing it) just to create the man pages. The man pages are no longer automatically created in the build process. The man/ directory has been removed. The man page templates have been moved to data/. New unexported module: Text.Pandoc.ManPages. Text.Pandoc.Data now exports readmeFile, and `readDataFile` knows how to find README. Closes #2190.
Diffstat (limited to 'man/make-pandoc-man-pages.hs')
-rw-r--r--man/make-pandoc-man-pages.hs104
1 files changed, 0 insertions, 104 deletions
diff --git a/man/make-pandoc-man-pages.hs b/man/make-pandoc-man-pages.hs
deleted file mode 100644
index 60baff81e..000000000
--- a/man/make-pandoc-man-pages.hs
+++ /dev/null
@@ -1,104 +0,0 @@
-{-# LANGUAGE CPP #-}
--- Create pandoc.1 man and pandoc_markdown.5 man pages from README
-import Text.Pandoc
-import Text.Pandoc.Error (handleError)
-import qualified Text.Pandoc.UTF8 as UTF8
-import Data.Char (toUpper)
-import Control.Monad
-import System.FilePath
-import System.Environment (getArgs)
-import Text.Pandoc.Shared (normalize)
-import Data.Maybe ( catMaybes )
-import Prelude hiding (catch)
-import Control.Exception ( catch )
-import System.IO.Error ( isDoesNotExistError )
-#if MIN_VERSION_directory(1,2,0)
-import Data.Time.Clock (UTCTime(..))
-#else
-import System.Time (ClockTime(..))
-#endif
-import System.Directory
-
-main :: IO ()
-main = do
- ds1 <- modifiedDependencies ("man" </> "man1" </> "pandoc.1")
- ["README", "man" </> "man1" </> "pandoc.1.template"]
- ds2 <- modifiedDependencies ("man" </> "man5" </> "pandoc_markdown.5")
- ["README", "man" </> "man5" </> "pandoc_markdown.5.template"]
-
- unless (null ds1 && null ds2) $ do
- rmContents <- UTF8.readFile "README"
- let (Pandoc meta blocks) = normalize $ handleError $ readMarkdown def rmContents
- let manBlocks = removeSect [Str "Wrappers"]
- $ removeSect [Str "Pandoc's",Space,Str "markdown"] blocks
- let syntaxBlocks = extractSect [Str "Pandoc's",Space,Str "markdown"] blocks
- args <- getArgs
- let verbose = "--verbose" `elem` args
- unless (null ds1) $
- makeManPage verbose ("man" </> "man1" </> "pandoc.1") meta manBlocks
- unless (null ds2) $
- makeManPage verbose ("man" </> "man5" </> "pandoc_markdown.5") meta syntaxBlocks
-
-makeManPage :: Bool -> FilePath -> Meta -> [Block] -> IO ()
-makeManPage verbose page meta blocks = do
- let templ = page <.> "template"
- manTemplate <- UTF8.readFile templ
- writeManPage page manTemplate (Pandoc meta blocks)
- when verbose $ putStrLn $ "Created " ++ page
-
-writeManPage :: FilePath -> String -> Pandoc -> IO ()
-writeManPage page templ doc = do
- let version = pandocVersion
- let opts = def{ writerStandalone = True
- , writerTemplate = templ
- , writerVariables = [("version",version)] }
- let manPage = writeMan opts $
- bottomUp (concatMap removeLinks) $
- bottomUp capitalizeHeaders doc
- UTF8.writeFile page manPage
-
-removeLinks :: Inline -> [Inline]
-removeLinks (Link l _) = l
-removeLinks x = [x]
-
-capitalizeHeaders :: Block -> Block
-capitalizeHeaders (Header 1 attr xs) = Header 1 attr $ bottomUp capitalize xs
-capitalizeHeaders x = x
-
-capitalize :: Inline -> Inline
-capitalize (Str xs) = Str $ map toUpper xs
-capitalize x = x
-
-removeSect :: [Inline] -> [Block] -> [Block]
-removeSect ils (Header 1 _ x:xs) | x == ils =
- dropWhile (not . isHeader1) xs
-removeSect ils (x:xs) = x : removeSect ils xs
-removeSect _ [] = []
-
-extractSect :: [Inline] -> [Block] -> [Block]
-extractSect ils (Header 1 _ z:xs) | z == ils =
- bottomUp promoteHeader $ takeWhile (not . isHeader1) xs
- where promoteHeader (Header n attr x) = Header (n-1) attr x
- promoteHeader x = x
-extractSect ils (x:xs) = extractSect ils xs
-extractSect _ [] = []
-
-isHeader1 :: Block -> Bool
-isHeader1 (Header 1 _ _ ) = True
-isHeader1 _ = False
-
-
--- | Returns a list of 'dependencies' that have been modified after 'file'.
-modifiedDependencies :: FilePath -> [FilePath] -> IO [FilePath]
-modifiedDependencies file dependencies = do
- fileModTime <- catch (getModificationTime file) $
- \e -> if isDoesNotExistError e
-#if MIN_VERSION_directory(1,2,0)
- then return (UTCTime (toEnum 0) 0) -- the minimum ClockTime
-#else
- then return (TOD 0 0) -- the minimum ClockTime
-#endif
- else ioError e
- depModTimes <- mapM getModificationTime dependencies
- let modified = zipWith (\dep time -> if time > fileModTime then Just dep else Nothing) dependencies depModTimes
- return $ catMaybes modified