Org reader: allow short hand for single-line raw blocks
Single-line raw blocks can be given via `#+FORMAT: raw line`, where `FORMAT` must be one of `latex`, `beamer`, `html`, or `texinfo`. Closes: #3366
This commit is contained in:
parent
aad7c3bf54
commit
5729f1f2ea
3 changed files with 29 additions and 8 deletions
|
@ -2,7 +2,7 @@
|
|||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE ViewPatterns #-}
|
||||
{-
|
||||
Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
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
|
||||
|
@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
|
||||
{- |
|
||||
Module : Text.Pandoc.Readers.Org.Options
|
||||
Copyright : Copyright (C) 2014-2016 Albert Krewinkel
|
||||
Copyright : Copyright (C) 2014-2017 Albert Krewinkel
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -35,7 +35,7 @@ module Text.Pandoc.Readers.Org.Blocks
|
|||
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
import Text.Pandoc.Readers.Org.Inlines
|
||||
import Text.Pandoc.Readers.Org.Meta ( metaExport, metaLine )
|
||||
import Text.Pandoc.Readers.Org.Meta ( metaExport, metaKey, metaLine )
|
||||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
import Text.Pandoc.Readers.Org.Shared
|
||||
|
@ -679,7 +679,15 @@ exampleCode = B.codeBlockWith ("", ["example"], [])
|
|||
--
|
||||
|
||||
specialLine :: OrgParser (F Blocks)
|
||||
specialLine = fmap return . try $ metaLine <|> commentLine
|
||||
specialLine = fmap return . try $ rawExportLine <|> metaLine <|> commentLine
|
||||
|
||||
rawExportLine :: OrgParser Blocks
|
||||
rawExportLine = try $ do
|
||||
metaLineStart
|
||||
key <- metaKey
|
||||
if key `elem` ["latex", "html", "texinfo", "beamer"]
|
||||
then B.rawBlock key <$> anyLine
|
||||
else mzero
|
||||
|
||||
commentLine :: OrgParser Blocks
|
||||
commentLine = commentLineStart *> anyLine *> pure mempty
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-
|
||||
Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
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
|
||||
|
@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
|
||||
{- |
|
||||
Module : Text.Pandoc.Readers.Org.Meta
|
||||
Copyright : Copyright (C) 2014-2016 Albert Krewinkel
|
||||
Copyright : Copyright (C) 2014-2017 Albert Krewinkel
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -28,8 +28,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Parsers for Org-mode meta declarations.
|
||||
-}
|
||||
module Text.Pandoc.Readers.Org.Meta
|
||||
( metaLine
|
||||
, metaExport
|
||||
( metaExport
|
||||
, metaKey
|
||||
, metaLine
|
||||
) where
|
||||
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
|
|
|
@ -1605,6 +1605,18 @@ tests =
|
|||
] =?>
|
||||
rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n"
|
||||
|
||||
, "Raw LaTeX line" =:
|
||||
"#+LATEX: \\let\\foo\\bar" =?>
|
||||
rawBlock "latex" "\\let\\foo\\bar"
|
||||
|
||||
, "Raw Beamer line" =:
|
||||
"#+beamer: \\pause" =?>
|
||||
rawBlock "beamer" "\\pause"
|
||||
|
||||
, "Raw HTML line" =:
|
||||
"#+HTML: <aside>not important</aside>" =?>
|
||||
rawBlock "html" "<aside>not important</aside>"
|
||||
|
||||
, "Export block HTML" =:
|
||||
unlines [ "#+BEGIN_export html"
|
||||
, "<samp>Hello, World!</samp>"
|
||||
|
|
Loading…
Reference in a new issue