aboutsummaryrefslogtreecommitdiff
path: root/man/make-pandoc-man-pages.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-10-15 21:26:24 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-10-15 21:26:24 -0700
commitb3ad94bde9e2d21a7b3823412197976b5454fdbd (patch)
tree88a27a870fa26cef64596e1cc5e969f83a0a2a77 /man/make-pandoc-man-pages.hs
parent6f9151c64ee16819d99ae4c9d0bef8fb9083d936 (diff)
downloadpandoc-b3ad94bde9e2d21a7b3823412197976b5454fdbd.tar.gz
Moved man page creation out of Setup.hs.
* MakeManPage.hs has been transformed into man/make-pandoc-man-pages.hs. * There is now a cabal stanza for this, so the dependencies are handled by cabal. * Special treatment in Setup.hs ensures that this never gets installed; it is built and used to create the man pages. * Setup.hs cleaned up.
Diffstat (limited to 'man/make-pandoc-man-pages.hs')
-rw-r--r--man/make-pandoc-man-pages.hs98
1 files changed, 98 insertions, 0 deletions
diff --git a/man/make-pandoc-man-pages.hs b/man/make-pandoc-man-pages.hs
new file mode 100644
index 000000000..b94af744e
--- /dev/null
+++ b/man/make-pandoc-man-pages.hs
@@ -0,0 +1,98 @@
+-- Create pandoc.1 man and pandoc_markdown.5 man pages from README
+import Text.Pandoc
+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 Data.Time.Clock (UTCTime(..))
+import Prelude hiding (catch)
+import Control.Exception ( catch )
+import System.IO.Error ( isDoesNotExistError )
+import System.Time (ClockTime(..))
+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) = 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 opts = def{ writerStandalone = True
+ , writerTemplate = templ }
+ 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 xs) = Header 1 $ 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) | normalize x == normalize ils =
+ dropWhile (not . isHeader1) xs
+removeSect ils (x:xs) = x : removeSect ils xs
+removeSect _ [] = []
+
+extractSect :: [Inline] -> [Block] -> [Block]
+extractSect ils (Header 1 z:xs) | normalize z == normalize ils =
+ bottomUp promoteHeader $ takeWhile (not . isHeader1) xs
+ where promoteHeader (Header n x) = Header (n-1) 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 __GLASGOW_HASKELL__ >= 706
+ 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
+