aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/ParserState.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2016-07-03 22:57:22 -0700
committerGitHub <noreply@github.com>2016-07-03 22:57:22 -0700
commite548b8df072c4eecfeb43f94c6517c35d5eba30c (patch)
tree93250a991695b6b4a3c19f805938955eb1b3d728 /src/Text/Pandoc/Readers/Org/ParserState.hs
parent4099b2dca469b8683632c60b05474f5f2b25fb36 (diff)
parent5ffa4abf727779cee317aab81c143e3e2d3cb7d6 (diff)
downloadpandoc-e548b8df072c4eecfeb43f94c6517c35d5eba30c.tar.gz
Merge pull request #3010 from tarleb/org-header-tree
Org reader: support archived trees, headline levels export setting
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/ParserState.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs99
1 files changed, 37 insertions, 62 deletions
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 0c58183f9..48e7717cd 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -40,14 +40,8 @@ module Text.Pandoc.Readers.Org.ParserState
, trimInlinesF
, runF
, returnF
- , ExportSettingSetter
, ExportSettings (..)
- , setExportDrawers
- , setExportEmphasizedText
- , setExportSmartQuotes
- , setExportSpecialStrings
- , setExportSubSuperscripts
- , modifyExportSettings
+ , ArchivedTreesOption (..)
, optionsToParserState
) where
@@ -78,19 +72,6 @@ type OrgNoteTable = [OrgNoteRecord]
-- link-type, the corresponding function transforms the given link string.
type OrgLinkFormatters = M.Map String (String -> String)
--- | Export settings <http://orgmode.org/manual/Export-settings.html>
--- These settings can be changed via OPTIONS statements.
-data ExportSettings = ExportSettings
- { exportDrawers :: Either [String] [String]
- -- ^ Specify drawer names which should be exported. @Left@ names are
- -- explicitly excluded from the resulting output while @Right@ means that
- -- only the listed drawer names should be included.
- , exportEmphasizedText :: Bool -- ^ Parse emphasized text
- , exportSmartQuotes :: Bool -- ^ Parse quotes smartly
- , exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
- , exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
- }
-
-- | Org-mode parser state
data OrgParserState = OrgParserState
{ orgStateAnchorIds :: [String]
@@ -133,9 +114,6 @@ instance HasHeaderMap OrgParserState where
extractHeaderMap = orgStateHeaderMap
updateHeaderMap f s = s{ orgStateHeaderMap = f (orgStateHeaderMap s) }
-instance Default ExportSettings where
- def = defaultExportSettings
-
instance Default OrgParserState where
def = defaultOrgParserState
@@ -157,53 +135,50 @@ defaultOrgParserState = OrgParserState
, orgStateParserContext = NullState
}
+optionsToParserState :: ReaderOptions -> OrgParserState
+optionsToParserState opts =
+ def { orgStateOptions = opts }
+
+--
+-- Export Settings
+--
+
+-- | Options for the way archived trees are handled.
+data ArchivedTreesOption =
+ ArchivedTreesExport -- ^ Export the complete tree
+ | ArchivedTreesNoExport -- ^ Exclude archived trees from exporting
+ | ArchivedTreesHeadlineOnly -- ^ Export only the headline, discard the contents
+
+-- | Export settings <http://orgmode.org/manual/Export-settings.html>
+-- These settings can be changed via OPTIONS statements.
+data ExportSettings = ExportSettings
+ { exportArchivedTrees :: ArchivedTreesOption -- ^ How to treat archived trees
+ , exportDrawers :: Either [String] [String]
+ -- ^ Specify drawer names which should be exported. @Left@ names are
+ -- explicitly excluded from the resulting output while @Right@ means that
+ -- only the listed drawer names should be included.
+ , exportEmphasizedText :: Bool -- ^ Parse emphasized text
+ , exportHeadlineLevels :: Int
+ -- ^ Maximum depth of headlines, deeper headlines are convert to list
+ , exportSmartQuotes :: Bool -- ^ Parse quotes smartly
+ , exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
+ , exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
+ }
+
+instance Default ExportSettings where
+ def = defaultExportSettings
+
defaultExportSettings :: ExportSettings
defaultExportSettings = ExportSettings
- { exportDrawers = Left ["LOGBOOK"]
+ { exportArchivedTrees = ArchivedTreesHeadlineOnly
+ , exportDrawers = Left ["LOGBOOK"]
, exportEmphasizedText = True
+ , exportHeadlineLevels = 3
, exportSmartQuotes = True
, exportSpecialStrings = True
, exportSubSuperscripts = True
}
-optionsToParserState :: ReaderOptions -> OrgParserState
-optionsToParserState opts =
- def { orgStateOptions = opts }
-
-
---
--- Setter for exporting options
---
-type ExportSettingSetter a = a -> ExportSettings -> ExportSettings
-
--- | Set export options for drawers. See the @exportDrawers@ in ADT
--- @ExportSettings@ for details.
-setExportDrawers :: ExportSettingSetter (Either [String] [String])
-setExportDrawers val es = es { exportDrawers = val }
-
--- | Set export options for emphasis parsing.
-setExportEmphasizedText :: ExportSettingSetter Bool
-setExportEmphasizedText val es = es { exportEmphasizedText = val }
-
--- | Set export options for parsing of smart quotes.
-setExportSmartQuotes :: ExportSettingSetter Bool
-setExportSmartQuotes val es = es { exportSmartQuotes = val }
-
--- | Set export options for parsing of special strings (like em/en dashes or
--- ellipses).
-setExportSpecialStrings :: ExportSettingSetter Bool
-setExportSpecialStrings val es = es { exportSpecialStrings = val }
-
--- | Set export options for sub/superscript parsing. The short syntax will
--- not be parsed if this is set set to @False@.
-setExportSubSuperscripts :: ExportSettingSetter Bool
-setExportSubSuperscripts val es = es { exportSubSuperscripts = val }
-
--- | Modify a parser state
-modifyExportSettings :: ExportSettingSetter a -> a -> OrgParserState -> OrgParserState
-modifyExportSettings setter val state =
- state { orgStateExportSettings = setter val . orgStateExportSettings $ state }
-
--
-- Parser state reader