2012-04-02 06:09:10 +02:00
|
|
|
-- Create pandoc.1 man and pandoc_markdown.5 man pages from README
|
2010-12-07 21:10:07 +01:00
|
|
|
import Text.Pandoc
|
|
|
|
import Data.ByteString.UTF8 (toString, fromString)
|
|
|
|
import Data.Char (toUpper)
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import Control.Monad
|
|
|
|
import System.FilePath
|
2011-01-28 20:55:11 +01:00
|
|
|
import System.Environment (getArgs)
|
|
|
|
import Text.Pandoc.Shared (normalize)
|
|
|
|
import System.Directory (getModificationTime)
|
|
|
|
import System.IO.Error (isDoesNotExistError)
|
|
|
|
import System.Time (ClockTime(..))
|
|
|
|
import Data.Maybe (catMaybes)
|
2012-07-25 04:28:51 +02:00
|
|
|
import qualified Control.Exception as E
|
2010-12-07 21:10:07 +01:00
|
|
|
|
|
|
|
main = do
|
|
|
|
rmContents <- liftM toString $ B.readFile "README"
|
|
|
|
let (Pandoc meta blocks) = readMarkdown defaultParserState rmContents
|
2011-01-28 20:55:11 +01:00
|
|
|
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
|
|
|
|
makeManPage verbose ("man" </> "man1" </> "pandoc.1")
|
|
|
|
meta manBlocks
|
|
|
|
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"
|
|
|
|
modDeps <- modifiedDependencies page ["README", templ]
|
|
|
|
unless (null modDeps) $ do
|
|
|
|
manTemplate <- liftM toString $ B.readFile templ
|
|
|
|
writeManPage page manTemplate (Pandoc meta blocks)
|
|
|
|
when verbose $
|
|
|
|
putStrLn $ "Created " ++ page
|
|
|
|
|
|
|
|
writeManPage :: FilePath -> String -> Pandoc -> IO ()
|
|
|
|
writeManPage page templ doc = do
|
2010-12-07 21:10:07 +01:00
|
|
|
let opts = defaultWriterOptions{ writerStandalone = True
|
2011-01-28 20:55:11 +01:00
|
|
|
, writerTemplate = templ }
|
2010-12-07 21:10:07 +01:00
|
|
|
let manPage = writeMan opts $
|
2011-01-28 20:55:11 +01:00
|
|
|
bottomUp (concatMap removeLinks) $
|
|
|
|
bottomUp capitalizeHeaders doc
|
|
|
|
B.writeFile page $ fromString manPage
|
|
|
|
|
|
|
|
-- | Returns a list of 'dependencies' that have been modified after 'file'.
|
|
|
|
modifiedDependencies :: FilePath -> [FilePath] -> IO [FilePath]
|
|
|
|
modifiedDependencies file dependencies = do
|
2012-07-25 04:28:51 +02:00
|
|
|
fileModTime <- E.catch (getModificationTime file) $
|
2011-01-28 20:55:11 +01:00
|
|
|
\e -> if isDoesNotExistError e
|
|
|
|
then return (TOD 0 0) -- the minimum ClockTime
|
|
|
|
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
|
2010-12-07 21:10:07 +01:00
|
|
|
|
|
|
|
removeLinks :: Inline -> [Inline]
|
|
|
|
removeLinks (Link l _) = l
|
|
|
|
removeLinks x = [x]
|
|
|
|
|
|
|
|
capitalizeHeaders :: Block -> Block
|
2010-12-24 22:39:27 +01:00
|
|
|
capitalizeHeaders (Header 1 xs) = Header 1 $ bottomUp capitalize xs
|
2010-12-07 21:10:07 +01:00
|
|
|
capitalizeHeaders x = x
|
|
|
|
|
|
|
|
capitalize :: Inline -> Inline
|
|
|
|
capitalize (Str xs) = Str $ map toUpper xs
|
|
|
|
capitalize x = x
|
|
|
|
|
2011-01-28 20:55:11 +01:00
|
|
|
removeSect :: [Inline] -> [Block] -> [Block]
|
|
|
|
removeSect ils (Header 1 x:xs) | normalize x == normalize ils =
|
2011-01-29 05:01:47 +01:00
|
|
|
dropWhile (not . isHeader1) xs
|
2011-01-28 20:55:11 +01:00
|
|
|
removeSect ils (x:xs) = x : removeSect ils xs
|
|
|
|
removeSect _ [] = []
|
|
|
|
|
|
|
|
extractSect :: [Inline] -> [Block] -> [Block]
|
2011-01-29 05:01:47 +01:00
|
|
|
extractSect ils (Header 1 z:xs) | normalize z == normalize ils =
|
|
|
|
bottomUp promoteHeader $ takeWhile (not . isHeader1) xs
|
2011-01-28 20:55:11 +01:00
|
|
|
where promoteHeader (Header n x) = Header (n-1) x
|
|
|
|
promoteHeader x = x
|
|
|
|
extractSect ils (x:xs) = extractSect ils xs
|
|
|
|
extractSect _ [] = []
|
|
|
|
|
2011-01-29 05:01:47 +01:00
|
|
|
isHeader1 :: Block -> Bool
|
|
|
|
isHeader1 (Header 1 _) = True
|
|
|
|
isHeader1 _ = False
|
|
|
|
|