diff options
| author | Albert Krewinkel <albert@zeitkraut.de> | 2017-01-19 20:27:58 +0100 | 
|---|---|---|
| committer | Albert Krewinkel <albert@zeitkraut.de> | 2017-01-19 20:33:05 +0100 | 
| commit | 5729f1f2eaf1665be3fcbf92917503bdd15d1995 (patch) | |
| tree | 38b8e269af9f77aee626f44f2312f208dcd7a815 | |
| parent | aad7c3bf542b082f2091faa663787c803e8cd844 (diff) | |
| download | pandoc-5729f1f2eaf1665be3fcbf92917503bdd15d1995.tar.gz | |
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
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 16 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Meta.hs | 9 | ||||
| -rw-r--r-- | tests/Tests/Readers/Org.hs | 12 | 
3 files changed, 29 insertions, 8 deletions
| diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index c217949d8..484d97482 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index bbbb216a0..1fea3e890 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -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 diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index 0518f6932..72b7e2601 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -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>" | 
