summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/ParserState.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/ParserState.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs156
1 files changed, 90 insertions, 66 deletions
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 38f95ca95..6316766fa 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-
-Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+Copyright (C) 2014-2018 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,8 +19,8 @@ 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
+ Module : Text.Pandoc.Readers.Org.ParserState
+ Copyright : Copyright (C) 2014-2018 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -30,16 +29,21 @@ Define the Org-mode parser state.
-}
module Text.Pandoc.Readers.Org.ParserState
( OrgParserState (..)
+ , defaultOrgParserState
, OrgParserLocal (..)
, OrgNoteRecord
, HasReaderOptions (..)
, HasQuoteContext (..)
+ , HasMacros (..)
, TodoMarker (..)
, TodoSequence
, TodoState (..)
, activeTodoMarkers
, registerTodoSequence
- , F(..)
+ , MacroExpander
+ , lookupMacro
+ , registerMacro
+ , F
, askF
, asksF
, trimInlinesF
@@ -50,24 +54,28 @@ module Text.Pandoc.Readers.Org.ParserState
, optionsToParserState
) where
-import Control.Monad (liftM, liftM2)
-import Control.Monad.Reader (Reader, runReader, ask, asks, local)
+import Control.Monad.Reader (ReaderT, asks, local)
-import Data.Default (Default(..))
+import Data.Default (Default (..))
import qualified Data.Map as M
import qualified Data.Set as Set
-
-import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
-import Text.Pandoc.Definition ( Meta(..), nullMeta )
-import Text.Pandoc.Options ( ReaderOptions(..) )
-import Text.Pandoc.Parsing ( HasHeaderMap(..)
- , HasIdentifierList(..)
- , HasLastStrPosition(..)
- , HasQuoteContext(..)
- , HasReaderOptions(..)
- , ParserContext(..)
- , QuoteContext(..)
- , SourcePos )
+import Data.Text (Text)
+
+import Text.Pandoc.Builder (Blocks, Inlines)
+import Text.Pandoc.Definition (Meta (..), nullMeta)
+import Text.Pandoc.Logging
+import Text.Pandoc.Options (ReaderOptions (..))
+import Text.Pandoc.Parsing (Future, HasHeaderMap (..), HasIdentifierList (..),
+ HasIncludeFiles (..), HasLastStrPosition (..),
+ HasLogMessages (..), HasMacros (..),
+ HasQuoteContext (..), HasReaderOptions (..),
+ ParserContext (..), QuoteContext (..), SourcePos,
+ askF, asksF, returnF, runF, trimInlinesF)
+import Text.Pandoc.Readers.LaTeX.Types (Macro)
+
+-- | This is used to delay evaluation until all relevant information has been
+-- parsed and made available in the parser state.
+type F = Future OrgParserState
-- | An inline note / footnote containing the note key and its (inline) value.
type OrgNoteRecord = (String, F Blocks)
@@ -76,6 +84,8 @@ type OrgNoteTable = [OrgNoteRecord]
-- | Map of functions for link transformations. The map key is refers to the
-- link-type, the corresponding function transforms the given link string.
type OrgLinkFormatters = M.Map String (String -> String)
+-- | Macro expander function
+type MacroExpander = [String] -> String
-- | The states in which a todo item can be
data TodoState = Todo | Done
@@ -95,22 +105,34 @@ type TodoSequence = [TodoMarker]
data OrgParserState = OrgParserState
{ orgStateAnchorIds :: [String]
, orgStateEmphasisCharStack :: [Char]
+ , orgStateEmphasisPreChars :: [Char] -- ^ Chars allowed to occur before
+ -- emphasis; spaces and newlines are
+ -- always ok in addition to what is
+ -- specified here.
+ , orgStateEmphasisPostChars :: [Char] -- ^ Chars allowed at after emphasis
, orgStateEmphasisNewlines :: Maybe Int
, orgStateExportSettings :: ExportSettings
, orgStateHeaderMap :: M.Map Inlines String
, orgStateIdentifiers :: Set.Set String
+ , orgStateIncludeFiles :: [String]
, orgStateLastForbiddenCharPos :: Maybe SourcePos
, orgStateLastPreCharPos :: Maybe SourcePos
, orgStateLastStrPos :: Maybe SourcePos
, orgStateLinkFormatters :: OrgLinkFormatters
+ , orgStateMacros :: M.Map String MacroExpander
+ , orgStateMacroDepth :: Int
, orgStateMeta :: F Meta
, orgStateNotes' :: OrgNoteTable
, orgStateOptions :: ReaderOptions
, orgStateParserContext :: ParserContext
, orgStateTodoSequences :: [TodoSequence]
+ , orgLogMessages :: [LogMessage]
+ , orgMacros :: M.Map Text Macro
}
-data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext }
+data OrgParserLocal = OrgParserLocal
+ { orgLocalQuoteContext :: QuoteContext
+ }
instance Default OrgParserLocal where
def = OrgParserLocal NoQuote
@@ -122,7 +144,7 @@ instance HasLastStrPosition OrgParserState where
getLastStrPos = orgStateLastStrPos
setLastStrPos pos st = st{ orgStateLastStrPos = Just pos }
-instance HasQuoteContext st (Reader OrgParserLocal) where
+instance Monad m => HasQuoteContext st (ReaderT OrgParserLocal m) where
getQuoteContext = asks orgLocalQuoteContext
withQuoteContext q = local (\s -> s{orgLocalQuoteContext = q})
@@ -134,26 +156,47 @@ instance HasHeaderMap OrgParserState where
extractHeaderMap = orgStateHeaderMap
updateHeaderMap f s = s{ orgStateHeaderMap = f (orgStateHeaderMap s) }
+instance HasLogMessages OrgParserState where
+ addLogMessage msg st = st{ orgLogMessages = msg : orgLogMessages st }
+ getLogMessages st = reverse $ orgLogMessages st
+
+instance HasMacros OrgParserState where
+ extractMacros st = orgMacros st
+ updateMacros f st = st{ orgMacros = f (orgMacros 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
defaultOrgParserState :: OrgParserState
defaultOrgParserState = OrgParserState
{ orgStateAnchorIds = []
+ , orgStateEmphasisPreChars = "-\t ('\"{"
+ , orgStateEmphasisPostChars = "-\t\n .,:!?;'\")}["
, orgStateEmphasisCharStack = []
, orgStateEmphasisNewlines = Nothing
, orgStateExportSettings = def
, orgStateHeaderMap = M.empty
, orgStateIdentifiers = Set.empty
+ , orgStateIncludeFiles = []
, orgStateLastForbiddenCharPos = Nothing
, orgStateLastPreCharPos = Nothing
, orgStateLastStrPos = Nothing
, orgStateLinkFormatters = M.empty
+ , orgStateMacros = M.empty
+ , orgStateMacroDepth = 0
, orgStateMeta = return nullMeta
, orgStateNotes' = []
, orgStateOptions = def
, orgStateParserContext = NullState
, orgStateTodoSequences = []
+ , orgLogMessages = []
+ , orgMacros = M.empty
}
optionsToParserState :: ReaderOptions -> OrgParserState
@@ -177,6 +220,15 @@ activeTodoSequences st =
activeTodoMarkers :: OrgParserState -> TodoSequence
activeTodoMarkers = concat . activeTodoSequences
+lookupMacro :: String -> OrgParserState -> Maybe MacroExpander
+lookupMacro macroName = M.lookup macroName . orgStateMacros
+
+registerMacro :: (String, MacroExpander) -> OrgParserState -> OrgParserState
+registerMacro (name, expander) st =
+ let curMacros = orgStateMacros st
+ in st{ orgStateMacros = M.insert name expander curMacros }
+
+
--
-- Export Settings
@@ -191,20 +243,22 @@ data ArchivedTreesOption =
-- | 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]
+ { 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
+ , 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
- , exportWithAuthor :: Bool -- ^ Include author in final meta-data
- , exportWithCreator :: Bool -- ^ Include creator in final meta-data
- , exportWithEmail :: Bool -- ^ Include email in final meta-data
+ , exportPreserveBreaks :: Bool -- ^ Whether to preserve linebreaks
+ , exportSmartQuotes :: Bool -- ^ Parse quotes smartly
+ , exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
+ , exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
+ , exportWithAuthor :: Bool -- ^ Include author in final meta-data
+ , exportWithCreator :: Bool -- ^ Include creator in final meta-data
+ , exportWithEmail :: Bool -- ^ Include email in final meta-data
+ , exportWithTags :: Bool -- ^ Keep tags as part of headlines
, exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers
}
@@ -217,43 +271,13 @@ defaultExportSettings = ExportSettings
, exportDrawers = Left ["LOGBOOK"]
, exportEmphasizedText = True
, exportHeadlineLevels = 3
- , exportSmartQuotes = True
+ , exportPreserveBreaks = False
+ , exportSmartQuotes = False
, exportSpecialStrings = True
, exportSubSuperscripts = True
, exportWithAuthor = True
, exportWithCreator = True
, exportWithEmail = True
+ , exportWithTags = True
, exportWithTodoKeywords = True
}
-
-
---
--- Parser state reader
---
-
--- | Reader monad wrapping the parser state. This is used to delay evaluation
--- until all relevant information has been parsed and made available in the
--- parser state. See also the newtype of the same name in
--- Text.Pandoc.Parsing.
-newtype F a = F { unF :: Reader OrgParserState a
- } deriving (Functor, Applicative, Monad)
-
-instance Monoid a => Monoid (F a) where
- mempty = return mempty
- mappend = liftM2 mappend
- mconcat = fmap mconcat . sequence
-
-runF :: F a -> OrgParserState -> a
-runF = runReader . unF
-
-askF :: F OrgParserState
-askF = F ask
-
-asksF :: (OrgParserState -> a) -> F a
-asksF f = F $ asks f
-
-trimInlinesF :: F Inlines -> F Inlines
-trimInlinesF = liftM trimInlines
-
-returnF :: Monad m => a -> m (F a)
-returnF = return . return