From 3fa9a838c0b81e9487634cb82c78dda235452534 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 21 Oct 2018 13:09:13 -0700 Subject: Man reader: Support .so for include files. Closes #4986. --- src/Text/Pandoc/Readers/Man.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs index a47181692..20f0eda97 100644 --- a/src/Text/Pandoc/Readers/Man.hs +++ b/src/Text/Pandoc/Readers/Man.hs @@ -2,6 +2,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- Copyright (C) 2018 Yan Pashkovsky + and 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 @@ -37,6 +38,7 @@ module Text.Pandoc.Readers.Man (readMan) where import Prelude import Control.Monad (liftM, void, mzero, guard) import Control.Monad.Except (throwError) +import Text.Pandoc.Class (getResourcePath, readFileFromDirs) import Data.Char (isHexDigit, chr, ord) import Data.Default (Default) import Data.Maybe (catMaybes) @@ -278,10 +280,25 @@ lexMacro = do "\\#" -> return mempty "de" -> lexMacroDef args "sp" -> return $ singleTok MEmptyLine + "so" -> lexIncludeFile args _ -> resolveMacro macroName args where + lexIncludeFile :: PandocMonad m => [Arg] -> ManLexer m ManTokens + lexIncludeFile args = do + pos <- getPosition + case args of + (f:_) -> do + let fp = linePartsToString f + dirs <- getResourcePath + result <- readFileFromDirs dirs fp + case result of + Nothing -> report $ CouldNotLoadIncludeFile fp pos + Just s -> getInput >>= setInput . (s ++) + return mempty + [] -> return mempty + resolveMacro :: PandocMonad m => String -> [Arg] -> ManLexer m ManTokens resolveMacro macroName args = do -- cgit v1.2.3