From a04c15a422cac279e75b012db9614cdc85aa1188 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Jul 2015 11:21:34 -0700 Subject: New method for building man pages. + Removed `--man1`, `--man5` options (breaking change). + Removed `Text.Pandoc.ManPages` module (breaking API change). + Version bump to 1.15 because of the breaking changes, even though they involve features that have only been in pandoc for a day. + Makefile target for `man/man1/pandoc.1`. This uses pandoc to create the man page from README using a custom template and filters. + Added `man/` directory with template and filters needed to build man page. + We no longer have two man pages: pandoc.1 and pandoc_markdown.5. Now there is just pandoc.1, which has all the content from README. This change was needed because of the extensive cross-references between parts of the README. + Removed old `data/pandoc.1.template` and `data/pandoc_markdown.5.template`. --- src/Text/Pandoc/ManPages.hs | 101 -------------------------------------------- 1 file changed, 101 deletions(-) delete mode 100644 src/Text/Pandoc/ManPages.hs (limited to 'src') diff --git a/src/Text/Pandoc/ManPages.hs b/src/Text/Pandoc/ManPages.hs deleted file mode 100644 index cc5f162f8..000000000 --- a/src/Text/Pandoc/ManPages.hs +++ /dev/null @@ -1,101 +0,0 @@ -{-# LANGUAGE CPP #-} -{- -Copyright (C) 2013-2015 John MacFarlane - -This program is free software; you can redistribute it and/or modify -it under the terms of the GNU General Public License as published by -the Free Software Foundation; either version 2 of the License, or -(at your option) any later version. - -This program is distributed in the hope that it will be useful, -but WITHOUT ANY WARRANTY; without even the implied warranty of -MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -GNU General Public License for more details. - -You should have received a copy of the GNU General Public License -along with this program; if not, write to the Free Software -Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA --} - -{- | - Module : Text.Pandoc.ManPages - Copyright : Copyright (C) 2013-2015 John MacFarlane - License : GNU GPL, version 2 or above - - Maintainer : John MacFarlane - Stability : alpha - Portability : portable - -Functions to build pandoc's man pages (pandoc.1 and pandoc_markdown.5) -from pandoc's README. --} -module Text.Pandoc.ManPages ( - manPandoc1, - manPandocMarkdown5 - ) where -import Text.Pandoc -import Text.Pandoc.Error (handleError) -import Data.Char (toUpper) -import System.FilePath -import Text.Pandoc.Shared (normalize, readDataFileUTF8) - -manPandoc1 :: IO String -manPandoc1 = do - readme <- readDataFileUTF8 Nothing "README" - let (Pandoc meta blocks) = normalize $ handleError - $ readMarkdown def readme - let manBlocks = removeSect [Str "Wrappers"] - $ removeSect [Str "Pandoc's",Space,Str "markdown"] blocks - makeManPage "pandoc.1" meta manBlocks - -manPandocMarkdown5 :: IO String -manPandocMarkdown5 = do - readme <- readDataFileUTF8 Nothing "README" - let (Pandoc meta blocks) = normalize $ handleError - $ readMarkdown def readme - let syntaxBlocks = extractSect [Str "Pandoc's",Space,Str "markdown"] blocks - makeManPage "pandoc_markdown.5" meta syntaxBlocks - -makeManPage :: String -> Meta -> [Block] -> IO String -makeManPage page meta blocks = do - let templ = page <.> "template" - manTemplate <- readDataFileUTF8 Nothing templ - return $ writeManPage manTemplate (Pandoc meta blocks) - -writeManPage :: String -> Pandoc -> String -writeManPage templ doc = - writeMan def{ writerStandalone = True - , writerTemplate = templ - , writerVariables = [("version", pandocVersion)] } $ - bottomUp (concatMap removeLinks) $ - bottomUp capitalizeHeaders doc - -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 (_:xs) = extractSect ils xs -extractSect _ [] = [] - -isHeader1 :: Block -> Bool -isHeader1 (Header 1 _ _ ) = True -isHeader1 _ = False -- cgit v1.2.3