aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org
diff options
context:
space:
mode:
authorYan Pas <yanp.bugz@gmail.com>2018-10-07 18:10:01 +0300
committerYan Pas <yanp.bugz@gmail.com>2018-10-07 18:10:01 +0300
commit27467189ab184c5d098e244e01f7d1bfdb0d4d45 (patch)
treed1fb96ebbc49ee0c4e73ef354feddd521690d545 /src/Text/Pandoc/Readers/Org
parent4f3dd3b1af7217214287ab886147c5e33a54774d (diff)
parentbd8a66394bc25b52dca9ffd963a560a4ca492f9c (diff)
downloadpandoc-27467189ab184c5d098e244e01f7d1bfdb0d4d45.tar.gz
Merge branch 'master' into groff_reader
Diffstat (limited to 'src/Text/Pandoc/Readers/Org')
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs7
-rw-r--r--src/Text/Pandoc/Readers/Org/DocumentTree.hs139
-rw-r--r--src/Text/Pandoc/Readers/Org/ExportSettings.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs10
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs14
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs10
-rw-r--r--src/Text/Pandoc/Readers/Org/Parsing.hs15
-rw-r--r--src/Text/Pandoc/Readers/Org/Shared.hs4
8 files changed, 146 insertions, 55 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 888cd9307..1c52c3477 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -40,7 +40,7 @@ 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 (cleanLinkString, isImageFilename,
- originalLang, translateLang)
+ originalLang, translateLang, exportsCode)
import Text.Pandoc.Builder (Blocks, Inlines)
import Text.Pandoc.Class (PandocMonad)
@@ -314,9 +314,6 @@ codeBlock blockAttrs blockType = do
labelledBlock :: F Inlines -> F Blocks
labelledBlock = fmap (B.plain . B.spanWith ("", ["label"], []))
- exportsCode :: [(String, String)] -> Bool
- exportsCode = maybe True (`elem` ["code", "both"]) . lookup "exports"
-
exportsResults :: [(String, String)] -> Bool
exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports"
@@ -743,7 +740,7 @@ latexEnd envName = try $
--
--- Footnote defintions
+-- Footnote definitions
--
noteBlock :: PandocMonad m => OrgParser m (F Blocks)
noteBlock = try $ do
diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs
index c9465581a..7d55892fe 100644
--- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs
+++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -17,8 +16,7 @@ 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 #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Readers.Org.DocumentTree
Copyright : Copyright (C) 2014-2018 Albert Krewinkel
@@ -45,7 +43,7 @@ import Text.Pandoc.Readers.Org.BlockStarts
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
-import qualified Data.Map as Map
+import qualified Data.Set as Set
import qualified Text.Pandoc.Builder as B
--
@@ -60,7 +58,7 @@ documentTree :: PandocMonad m
documentTree blocks inline = do
initialBlocks <- blocks
headlines <- sequence <$> manyTill (headline blocks inline 1) eof
- title <- fmap (getTitle . unMeta) . orgStateMeta <$> getState
+ title <- fmap docTitle . orgStateMeta <$> getState
return $ do
headlines' <- headlines
initialBlocks' <- initialBlocks
@@ -70,19 +68,11 @@ documentTree blocks inline = do
, headlineTodoMarker = Nothing
, headlineText = B.fromList title'
, headlineTags = mempty
+ , headlinePlanning = emptyPlanning
, headlineProperties = mempty
, headlineContents = initialBlocks'
, headlineChildren = headlines'
}
- where
- getTitle :: Map.Map String MetaValue -> [Inline]
- getTitle metamap =
- case Map.lookup "title" metamap of
- Just (MetaInlines inlns) -> inlns
- _ -> []
-
-newtype Tag = Tag { fromTag :: String }
- deriving (Show, Eq)
-- | Create a tag containing the given string.
toTag :: String -> Tag
@@ -117,6 +107,7 @@ data Headline = Headline
, headlineTodoMarker :: Maybe TodoMarker
, headlineText :: Inlines
, headlineTags :: [Tag]
+ , headlinePlanning :: PlanningInfo -- ^ subtree planning information
, headlineProperties :: Properties
, headlineContents :: Blocks
, headlineChildren :: [Headline]
@@ -136,6 +127,7 @@ headline blocks inline lvl = try $ do
title <- trimInlinesF . mconcat <$> manyTill inline endOfTitle
tags <- option [] headerTags
newline
+ planning <- option emptyPlanning planningInfo
properties <- option mempty propertiesDrawer
contents <- blocks
children <- many (headline blocks inline (level + 1))
@@ -148,6 +140,7 @@ headline blocks inline lvl = try $ do
, headlineTodoMarker = todoKw
, headlineText = title'
, headlineTags = tags
+ , headlinePlanning = planning
, headlineProperties = properties
, headlineContents = contents'
, headlineChildren = children'
@@ -158,22 +151,27 @@ headline blocks inline lvl = try $ do
headerTags :: Monad m => OrgParser m [Tag]
headerTags = try $
- let tag = many1 (alphaNum <|> oneOf "@%#_") <* char ':'
+ let tag = orgTagWord <* char ':'
in map toTag <$> (skipSpaces *> char ':' *> many1 tag <* skipSpaces)
-- | Convert an Org mode headline (i.e. a document tree) into pandoc's Blocks
headlineToBlocks :: Monad m => Headline -> OrgParser m Blocks
-headlineToBlocks hdln@Headline {..} = do
- maxHeadlineLevels <- getExportSetting exportHeadlineLevels
+headlineToBlocks hdln = do
+ maxLevel <- getExportSetting exportHeadlineLevels
+ let tags = headlineTags hdln
+ let text = headlineText hdln
+ let level = headlineLevel hdln
+ shouldNotExport <- hasDoNotExportTag tags
case () of
- _ | any isNoExportTag headlineTags -> return mempty
- _ | any isArchiveTag headlineTags -> archivedHeadlineToBlocks hdln
- _ | isCommentTitle headlineText -> return mempty
- _ | headlineLevel >= maxHeadlineLevels -> headlineToHeaderWithList hdln
- _ | otherwise -> headlineToHeaderWithContents hdln
+ _ | shouldNotExport -> return mempty
+ _ | any isArchiveTag tags -> archivedHeadlineToBlocks hdln
+ _ | isCommentTitle text -> return mempty
+ _ | maxLevel <= level -> headlineToHeaderWithList hdln
+ _ | otherwise -> headlineToHeaderWithContents hdln
-isNoExportTag :: Tag -> Bool
-isNoExportTag = (== toTag "noexport")
+hasDoNotExportTag :: Monad m => [Tag] -> OrgParser m Bool
+hasDoNotExportTag tags = containsExcludedTag . orgStateExcludedTags <$> getState
+ where containsExcludedTag s = any (`Set.member` s) tags
isArchiveTag :: Tag -> Bool
isArchiveTag = (== toTag "ARCHIVE")
@@ -182,8 +180,9 @@ isArchiveTag = (== toTag "ARCHIVE")
-- FIXME: This accesses builder internals not intended for use in situations
-- like these. Replace once keyword parsing is supported.
isCommentTitle :: Inlines -> Bool
-isCommentTitle (B.toList -> (Str "COMMENT":_)) = True
-isCommentTitle _ = False
+isCommentTitle inlns = case B.toList inlns of
+ (Str "COMMENT":_) -> True
+ _ -> False
archivedHeadlineToBlocks :: Monad m => Headline -> OrgParser m Blocks
archivedHeadlineToBlocks hdln = do
@@ -194,17 +193,23 @@ archivedHeadlineToBlocks hdln = do
ArchivedTreesHeadlineOnly -> headlineToHeader hdln
headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks
-headlineToHeaderWithList hdln@Headline {..} = do
+headlineToHeaderWithList hdln = do
maxHeadlineLevels <- getExportSetting exportHeadlineLevels
header <- headlineToHeader hdln
- listElements <- mapM headlineToBlocks headlineChildren
+ listElements <- mapM headlineToBlocks (headlineChildren hdln)
+ planningBlock <- planningToBlock (headlinePlanning hdln)
let listBlock = if null listElements
then mempty
else B.orderedList listElements
- let headerText = if maxHeadlineLevels == headlineLevel
+ let headerText = if maxHeadlineLevels == headlineLevel hdln
then header
else flattenHeader header
- return $ headerText <> headlineContents <> listBlock
+ return . mconcat $
+ [ headerText
+ , headlineContents hdln
+ , planningBlock
+ , listBlock
+ ]
where
flattenHeader :: Blocks -> Blocks
flattenHeader blks =
@@ -213,27 +218,28 @@ headlineToHeaderWithList hdln@Headline {..} = do
_ -> mempty
headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks
-headlineToHeaderWithContents hdln@Headline {..} = do
+headlineToHeaderWithContents hdln = do
header <- headlineToHeader hdln
- childrenBlocks <- mconcat <$> mapM headlineToBlocks headlineChildren
- return $ header <> headlineContents <> childrenBlocks
+ planningBlock <- planningToBlock (headlinePlanning hdln)
+ childrenBlocks <- mconcat <$> mapM headlineToBlocks (headlineChildren hdln)
+ return $ header <> planningBlock <> headlineContents hdln <> childrenBlocks
headlineToHeader :: Monad m => Headline -> OrgParser m Blocks
-headlineToHeader Headline {..} = do
+headlineToHeader hdln = do
exportTodoKeyword <- getExportSetting exportWithTodoKeywords
exportTags <- getExportSetting exportWithTags
let todoText = if exportTodoKeyword
- then case headlineTodoMarker of
+ then case headlineTodoMarker hdln of
Just kw -> todoKeywordToInlines kw <> B.space
Nothing -> mempty
else mempty
- let text = todoText <> headlineText <>
+ let text = todoText <> headlineText hdln <>
if exportTags
- then tagsToInlines headlineTags
+ then tagsToInlines (headlineTags hdln)
else mempty
- let propAttr = propertiesToAttr headlineProperties
- attr <- registerHeader propAttr headlineText
- return $ B.headerWith attr headlineLevel text
+ let propAttr = propertiesToAttr (headlineProperties hdln)
+ attr <- registerHeader propAttr (headlineText hdln)
+ return $ B.headerWith attr (headlineLevel hdln) text
todoKeyword :: Monad m => OrgParser m TodoMarker
todoKeyword = try $ do
@@ -277,9 +283,60 @@ tagsToInlines tags =
tagSpan :: Tag -> Inlines -> Inlines
tagSpan t = B.spanWith ("", ["tag"], [("tag-name", fromTag t)])
+-- | Render planning info as a block iff the respective export setting is
+-- enabled.
+planningToBlock :: Monad m => PlanningInfo -> OrgParser m Blocks
+planningToBlock planning = do
+ includePlanning <- getExportSetting exportWithPlanning
+ return $
+ if includePlanning
+ then B.plain . mconcat . intersperse B.space . filter (/= mempty) $
+ [ datumInlines planningClosed "CLOSED"
+ , datumInlines planningDeadline "DEADLINE"
+ , datumInlines planningScheduled "SCHEDULED"
+ ]
+ else mempty
+ where
+ datumInlines field name =
+ case field planning of
+ Nothing -> mempty
+ Just time -> B.strong (B.str name <> B.str ":")
+ <> B.space
+ <> B.emph (B.str time)
+
+-- | An Org timestamp, including repetition marks. TODO: improve
+type Timestamp = String
+
+timestamp :: Monad m => OrgParser m Timestamp
+timestamp = try $ do
+ openChar <- oneOf "<["
+ let isActive = openChar == '<'
+ let closeChar = if isActive then '>' else ']'
+ content <- many1Till anyChar (char closeChar)
+ return (openChar : content ++ [closeChar])
+
+-- | Planning information for a subtree/headline.
+data PlanningInfo = PlanningInfo
+ { planningClosed :: Maybe Timestamp
+ , planningDeadline :: Maybe Timestamp
+ , planningScheduled :: Maybe Timestamp
+ }
+emptyPlanning :: PlanningInfo
+emptyPlanning = PlanningInfo Nothing Nothing Nothing
-
+-- | Read a single planning-related and timestamped line.
+planningInfo :: Monad m => OrgParser m PlanningInfo
+planningInfo = try $ do
+ updaters <- many1 planningDatum <* skipSpaces <* newline
+ return $ foldr ($) emptyPlanning updaters
+ where
+ planningDatum = skipSpaces *> choice
+ [ updateWith (\s p -> p { planningScheduled = Just s}) "SCHEDULED"
+ , updateWith (\d p -> p { planningDeadline = Just d}) "DEADLINE"
+ , updateWith (\c p -> p { planningClosed = Just c}) "CLOSED"
+ ]
+ updateWith fn cs = fn <$> (string cs *> char ':' *> skipSpaces *> timestamp)
-- | Read a :PROPERTIES: drawer and return the key/value pairs contained
-- within.
diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
index d02eb37c5..f79ee0d64 100644
--- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs
+++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
@@ -69,7 +69,7 @@ exportSetting = choice
, integerSetting "H" (\val es -> es { exportHeadlineLevels = val })
, ignoredSetting "inline"
, ignoredSetting "num"
- , ignoredSetting "p"
+ , booleanSetting "p" (\val es -> es { exportWithPlanning = val })
, ignoredSetting "pri"
, ignoredSetting "prop"
, ignoredSetting "stat"
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 7d1568b80..a5335ca57 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker)
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Readers.Org.Shared (cleanLinkString, isImageFilename,
- originalLang, translateLang)
+ originalLang, translateLang, exportsCode)
import Text.Pandoc.Builder (Inlines)
import qualified Text.Pandoc.Builder as B
@@ -510,7 +510,7 @@ anchor = try $ do
<* string ">>"
<* skipSpaces
--- | Replace every char but [a-zA-Z0-9_.-:] with a hypen '-'. This mirrors
+-- | Replace every char but [a-zA-Z0-9_.-:] with a hyphen '-'. This mirrors
-- the org function @org-export-solidify-link-text@.
solidify :: String -> String
@@ -525,11 +525,13 @@ inlineCodeBlock :: PandocMonad m => OrgParser m (F Inlines)
inlineCodeBlock = try $ do
string "src_"
lang <- many1 orgArgWordChar
- opts <- option [] $ enclosedByPair '[' ']' inlineBlockOption
+ opts <- option [] $ try (enclosedByPair '[' ']' inlineBlockOption)
+ <|> (mempty <$ string "[]")
inlineCode <- enclosedByPair '{' '}' (noneOf "\n\r")
let attrClasses = [translateLang lang]
let attrKeyVal = originalLang lang <> opts
- returnF $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode
+ let codeInlineBlck = B.codeWith ("", attrClasses, attrKeyVal) inlineCode
+ returnF $ (if exportsCode opts then codeInlineBlck else mempty)
where
inlineBlockOption :: PandocMonad m => OrgParser m (String, String)
inlineBlockOption = try $ do
diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs
index 965e33d94..cad1d7123 100644
--- a/src/Text/Pandoc/Readers/Org/Meta.hs
+++ b/src/Text/Pandoc/Readers/Org/Meta.hs
@@ -52,6 +52,7 @@ import Data.Char (toLower)
import Data.List (intersperse)
import Data.Maybe (fromMaybe)
import qualified Data.Map as M
+import qualified Data.Set as Set
import Network.HTTP (urlEncode)
-- | Returns the current meta, respecting export options.
@@ -158,6 +159,7 @@ optionLine = try $ do
"seq_todo" -> todoSequence >>= updateState . registerTodoSequence
"typ_todo" -> todoSequence >>= updateState . registerTodoSequence
"macro" -> macroDefinition >>= updateState . registerMacro
+ "exclude_tags" -> excludedTagList >>= updateState . setExcludedTags
"pandoc-emphasis-pre" -> emphChars >>= updateState . setEmphasisPreChar
"pandoc-emphasis-post" -> emphChars >>= updateState . setEmphasisPostChar
_ -> mzero
@@ -190,6 +192,18 @@ parseFormat = try $ replacePlain <|> replaceUrl <|> justAppend
rest = manyTill anyChar (eof <|> () <$ oneOf "\n\r")
tillSpecifier c = manyTill (noneOf "\n\r") (try $ string ('%':c:""))
+excludedTagList :: Monad m => OrgParser m [Tag]
+excludedTagList = do
+ skipSpaces
+ map Tag <$> many (orgTagWord <* skipSpaces) <* newline
+
+setExcludedTags :: [Tag] -> OrgParserState -> OrgParserState
+setExcludedTags tagList st =
+ let finalSet = if orgStateExcludedTagsChanged st
+ then foldr Set.insert (orgStateExcludedTags st) tagList
+ else Set.fromList tagList
+ in st { orgStateExcludedTags = finalSet, orgStateExcludedTagsChanged = True}
+
setEmphasisPreChar :: Maybe [Char] -> OrgParserState -> OrgParserState
setEmphasisPreChar csMb st =
let preChars = fromMaybe (orgStateEmphasisPostChars defaultOrgParserState) csMb
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 4cb5bb626..59478256f 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Readers.Org.ParserState
, defaultOrgParserState
, OrgParserLocal (..)
, OrgNoteRecord
+ , Tag(..)
, HasReaderOptions (..)
, HasQuoteContext (..)
, HasMacros (..)
@@ -88,6 +89,9 @@ type OrgNoteTable = [OrgNoteRecord]
type OrgLinkFormatters = M.Map String (String -> String)
-- | Macro expander function
type MacroExpander = [String] -> String
+-- | Tag
+newtype Tag = Tag { fromTag :: String }
+ deriving (Show, Eq, Ord)
-- | The states in which a todo item can be
data TodoState = Todo | Done
@@ -113,6 +117,8 @@ data OrgParserState = OrgParserState
-- specified here.
, orgStateEmphasisPostChars :: [Char] -- ^ Chars allowed at after emphasis
, orgStateEmphasisNewlines :: Maybe Int
+ , orgStateExcludedTags :: Set.Set Tag
+ , orgStateExcludedTagsChanged :: Bool
, orgStateExportSettings :: ExportSettings
, orgStateHeaderMap :: M.Map Inlines String
, orgStateIdentifiers :: Set.Set String
@@ -183,6 +189,8 @@ defaultOrgParserState = OrgParserState
, orgStateEmphasisCharStack = []
, orgStateEmphasisNewlines = Nothing
, orgStateExportSettings = def
+ , orgStateExcludedTags = Set.singleton $ Tag "noexport"
+ , orgStateExcludedTagsChanged = False
, orgStateHeaderMap = M.empty
, orgStateIdentifiers = Set.empty
, orgStateIncludeFiles = []
@@ -260,6 +268,7 @@ data ExportSettings = ExportSettings
, exportWithAuthor :: Bool -- ^ Include author in final meta-data
, exportWithCreator :: Bool -- ^ Include creator in final meta-data
, exportWithEmail :: Bool -- ^ Include email in final meta-data
+ , exportWithPlanning :: Bool -- ^ Keep planning info after headlines
, exportWithTags :: Bool -- ^ Keep tags as part of headlines
, exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers
}
@@ -280,6 +289,7 @@ defaultExportSettings = ExportSettings
, exportWithAuthor = True
, exportWithCreator = True
, exportWithEmail = True
+ , exportWithPlanning = False
, exportWithTags = True
, exportWithTodoKeywords = True
}
diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs
index e014de65e..52a346e36 100644
--- a/src/Text/Pandoc/Readers/Org/Parsing.hs
+++ b/src/Text/Pandoc/Readers/Org/Parsing.hs
@@ -46,6 +46,8 @@ module Text.Pandoc.Readers.Org.Parsing
, orgArgKey
, orgArgWord
, orgArgWordChar
+ , orgTagWord
+ , orgTagWordChar
-- * Re-exports from Text.Pandoc.Parser
, ParserContext (..)
, many1Till
@@ -137,14 +139,13 @@ anyLine =
<* updateLastPreCharPos
<* updateLastForbiddenCharPos
--- The version Text.Pandoc.Parsing cannot be used, as we need additional parts
--- of the state saved and restored.
+-- | Like @'Text.Pandoc.Parsing'@, but resets the position of the last character
+-- allowed before emphasised text.
parseFromString :: Monad m => OrgParser m a -> String -> OrgParser m a
parseFromString parser str' = do
- oldLastPreCharPos <- orgStateLastPreCharPos <$> getState
updateState $ \s -> s{ orgStateLastPreCharPos = Nothing }
result <- P.parseFromString parser str'
- updateState $ \s -> s{ orgStateLastPreCharPos = oldLastPreCharPos }
+ updateState $ \s -> s { orgStateLastPreCharPos = Nothing }
return result
-- | Skip one or more tab or space characters.
@@ -221,3 +222,9 @@ orgArgWord = many1 orgArgWordChar
-- | Chars treated as part of a word in plists.
orgArgWordChar :: Monad m => OrgParser m Char
orgArgWordChar = alphaNum <|> oneOf "-_"
+
+orgTagWord :: Monad m => OrgParser m String
+orgTagWord = many1 orgTagWordChar
+
+orgTagWordChar :: Monad m => OrgParser m Char
+orgTagWordChar = alphaNum <|> oneOf "@%#_"
diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs
index 17fe34738..71d1dd517 100644
--- a/src/Text/Pandoc/Readers/Org/Shared.hs
+++ b/src/Text/Pandoc/Readers/Org/Shared.hs
@@ -32,6 +32,7 @@ module Text.Pandoc.Readers.Org.Shared
, isImageFilename
, originalLang
, translateLang
+ , exportsCode
) where
import Prelude
@@ -96,3 +97,6 @@ translateLang cs =
"sh" -> "bash"
"sqlite" -> "sql"
_ -> cs
+
+exportsCode :: [(String, String)] -> Bool
+exportsCode = maybe True (`elem` ["code", "both"]) . lookup "exports"