diff --git a/pandoc.cabal b/pandoc.cabal index a713e9372..bdee857b0 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -138,6 +138,9 @@ Extra-Source-Files: test/command/abbrevs test/command/sub-file-chapter-1.tex test/command/sub-file-chapter-2.tex + test/command/3510-subdoc.org + test/command/3510-export.latex + test/command/3510-src.hs test/docbook-reader.docbook test/docbook-xref.docbook test/html-reader.html diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 788ec26dc..e77a64efe 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ViewPatterns #-} {- Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -18,7 +15,9 @@ 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 -} - +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Readers.Org.Options Copyright : Copyright (C) 2014-2017 Albert Krewinkel @@ -274,6 +273,7 @@ block = choice [ mempty <$ blanklines , figure , example , genericDrawer + , include , specialLine , horizontalRule , list @@ -717,6 +717,34 @@ exampleCode = B.codeBlockWith ("", ["example"], []) specialLine :: PandocMonad m => OrgParser m (F Blocks) specialLine = fmap return . try $ rawExportLine <|> metaLine <|> commentLine +-- | Include the content of a file. +include :: PandocMonad m => OrgParser m (F Blocks) +include = try $ do + metaLineStart <* stringAnyCase "include:" <* skipSpaces + filename <- includeTarget + blockType <- optionMaybe $ skipSpaces *> many1 alphaNum + blocksParser <- case blockType of + Just "example" -> do + return $ pure . B.codeBlock <$> parseRaw + Just "export" -> do + format <- skipSpaces *> many (noneOf "\n\r\t ") + return $ pure . B.rawBlock format <$> parseRaw + Just "src" -> do + language <- skipSpaces *> many (noneOf "\n\r\t ") + let attr = (mempty, [language], mempty) + return $ pure . B.codeBlockWith attr <$> parseRaw + _ -> return $ pure . B.fromList <$> blockList + anyLine + insertIncludedFileF blocksParser ["."] filename + where + includeTarget :: PandocMonad m => OrgParser m FilePath + includeTarget = do + char '"' + manyTill (noneOf "\n\r\t") (char '"') + + parseRaw :: PandocMonad m => OrgParser m String + parseRaw = many anyChar + rawExportLine :: PandocMonad m => OrgParser m Blocks rawExportLine = try $ do metaLineStart diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index f530d1d03..51666fc64 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -66,7 +66,8 @@ import Text.Pandoc.Logging import Text.Pandoc.Parsing (HasHeaderMap (..), HasIdentifierList (..), HasLogMessages (..), HasLastStrPosition (..), HasQuoteContext (..), - HasReaderOptions (..), ParserContext (..), + HasReaderOptions (..), HasIncludeFiles (..), + ParserContext (..), QuoteContext (..), SourcePos, Future, askF, asksF, returnF, runF, trimInlinesF) @@ -106,6 +107,7 @@ data OrgParserState = OrgParserState , orgStateExportSettings :: ExportSettings , orgStateHeaderMap :: M.Map Inlines String , orgStateIdentifiers :: Set.Set String + , orgStateIncludeFiles :: [String] , orgStateLastForbiddenCharPos :: Maybe SourcePos , orgStateLastPreCharPos :: Maybe SourcePos , orgStateLastStrPos :: Maybe SourcePos @@ -148,6 +150,12 @@ instance HasLogMessages OrgParserState where addLogMessage msg st = st{ orgLogMessages = msg : orgLogMessages st } getLogMessages st = reverse $ orgLogMessages st +instance HasIncludeFiles OrgParserState where + getIncludeFiles = orgStateIncludeFiles + addIncludeFile f st = st { orgStateIncludeFiles = f : orgStateIncludeFiles st } + dropLatestIncludeFile st = + st { orgStateIncludeFiles = drop 1 $ orgStateIncludeFiles st } + instance Default OrgParserState where def = defaultOrgParserState @@ -159,6 +167,7 @@ defaultOrgParserState = OrgParserState , orgStateExportSettings = def , orgStateHeaderMap = M.empty , orgStateIdentifiers = Set.empty + , orgStateIncludeFiles = [] , orgStateLastForbiddenCharPos = Nothing , orgStateLastPreCharPos = Nothing , orgStateLastStrPos = Nothing diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 50f5ebae5..c25b215df 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -71,6 +71,7 @@ module Text.Pandoc.Readers.Org.Parsing , ellipses , citeKey , gridTableWith + , insertIncludedFileF -- * Re-exports from Text.Pandoc.Parsec , runParser , runParserT diff --git a/test/command/3510-export.latex b/test/command/3510-export.latex new file mode 100644 index 000000000..6d8636322 --- /dev/null +++ b/test/command/3510-export.latex @@ -0,0 +1 @@ +\emph{Hello} \ No newline at end of file diff --git a/test/command/3510-src.hs b/test/command/3510-src.hs new file mode 100644 index 000000000..ad5744b80 --- /dev/null +++ b/test/command/3510-src.hs @@ -0,0 +1 @@ +putStrLn outString diff --git a/test/command/3510-subdoc.org b/test/command/3510-subdoc.org new file mode 100644 index 000000000..5bcc6678a --- /dev/null +++ b/test/command/3510-subdoc.org @@ -0,0 +1,5 @@ +* Subsection + +Included text + +Lorem ipsum. diff --git a/test/command/3510.md b/test/command/3510.md new file mode 100644 index 000000000..7993db848 --- /dev/null +++ b/test/command/3510.md @@ -0,0 +1,20 @@ +See <http://orgmode.org/manual/Include-files.html> +``` +% pandoc -f org -t native +Text + +#+include: "command/3510-subdoc.org" + +#+INCLUDE: "command/3510-src.hs" src haskell +#+INCLUDE: "command/3510-export.latex" export latex + +More text +^D +[Para [Str "Text"] +,Header 1 ("subsection",[],[]) [Str "Subsection"] +,Para [Str "Included",Space,Str "text"] +,Plain [Str "Lorem",Space,Str "ipsum."] +,CodeBlock ("",["haskell"],[]) "putStrLn outString\n" +,RawBlock (Format "latex") "\\emph{Hello}" +,Para [Str "More",Space,Str "text"]] +```