diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
| -rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 672 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 462 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 2 | 
3 files changed, 548 insertions, 588 deletions
| diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index a36c2acde..638c8c9cf 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -31,7 +31,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.  module Text.Pandoc.Readers.Markdown ( readMarkdown,                                        readMarkdownWithWarnings ) where -import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate ) +import Data.List ( transpose, sortBy, intersperse, intercalate, elemIndex)  import qualified Data.Map as M  import Data.Scientific (coefficient, base10Exponent)  import Data.Ord ( comparing ) @@ -55,8 +55,9 @@ import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )  import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,                                    isTextTag, isCommentTag )  import Data.Monoid (mconcat, mempty) -import Control.Applicative ((<$>), (<*), (*>), (<$)) +import Control.Applicative ((<$>), (<*), (*>), (<$), (<*>))  import Control.Monad +import Control.Monad.Reader  import System.FilePath (takeExtension, addExtension)  import Text.HTML.TagSoup  import Text.HTML.TagSoup.Match (tagOpen) @@ -64,25 +65,29 @@ import qualified Data.Set as Set  import Text.Printf (printf)  import Debug.Trace (trace) -type MarkdownParser = Parser [Char] ParserState +type MarkdownParser a = ParserT [Char] ParserState (Reader ParserState) a  -- | Read markdown from an input string and return a Pandoc document.  readMarkdown :: ReaderOptions -- ^ Reader options               -> String        -- ^ String to parse (assuming @'\n'@ line endings)               -> Pandoc  readMarkdown opts s = -  (readWith parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n") +  runMarkdown opts s parseMarkdown  -- | Read markdown from an input string and return a pair of a Pandoc document  -- and a list of warnings.  readMarkdownWithWarnings :: ReaderOptions -- ^ Reader options                           -> String        -- ^ String to parse (assuming @'\n'@ line endings)                           -> (Pandoc, [String]) -readMarkdownWithWarnings opts s = -    (readWithWarnings parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n") +readMarkdownWithWarnings opts s = runMarkdown opts s (returnWarnings parseMarkdown) -trimInlinesF :: F Inlines -> F Inlines -trimInlinesF = liftM trimInlines +runMarkdown :: ReaderOptions -> String -> MarkdownParser a -> a +runMarkdown opts inp p = fst res +  where +    imd = readWithM (returnState p) def{ stateOptions = opts } (inp ++ "\n\n") +    res = runReader imd s +    s :: ParserState +    s   = snd $ runReader imd s  --  -- Constants and data structure definitions @@ -119,10 +124,10 @@ inList = do    ctx <- stateParserContext <$> getState    guard (ctx == ListItemState) -isNull :: F Inlines -> Bool -isNull ils = B.isNull $ runF ils def +isNull :: Inlines -> Bool +isNull = B.isNull -spnl :: Parser [Char] st () +spnl :: Monad m => ParserT [Char] st m ()  spnl = try $ do    skipSpaces    optional newline @@ -162,9 +167,9 @@ litChar = escapedChar'  -- | Parse a sequence of inline elements between square brackets,  -- including inlines between balanced pairs of square brackets. -inlinesInBalancedBrackets :: MarkdownParser (F Inlines) +inlinesInBalancedBrackets :: MarkdownParser Inlines  inlinesInBalancedBrackets = charsInBalancedBrackets >>= -  parseFromString (trimInlinesF . mconcat <$> many inline) +  parseFromString (trimInlines . mconcat <$> many inline)  charsInBalancedBrackets :: MarkdownParser [Char]  charsInBalancedBrackets = do @@ -181,16 +186,16 @@ charsInBalancedBrackets = do  -- document structure  -- -titleLine :: MarkdownParser (F Inlines) +titleLine :: MarkdownParser Inlines  titleLine = try $ do    char '%'    skipSpaces    res <- many $ (notFollowedBy newline >> inline)               <|> try (endline >> whitespace)    newline -  return $ trimInlinesF $ mconcat res +  return $ trimInlines $ mconcat res -authorsLine :: MarkdownParser (F [Inlines]) +authorsLine :: MarkdownParser [Inlines]  authorsLine = try $ do    char '%'    skipSpaces @@ -199,13 +204,13 @@ authorsLine = try $ do                         (char ';' <|>                          try (newline >> notFollowedBy blankline >> spaceChar))    newline -  return $ sequence $ filter (not . isNull) $ map (trimInlinesF . mconcat) authors +  return $ filter (not . isNull) $ map (trimInlines . mconcat) authors -dateLine :: MarkdownParser (F Inlines) +dateLine :: MarkdownParser Inlines  dateLine = try $ do    char '%'    skipSpaces -  trimInlinesF . mconcat <$> manyTill inline newline +  trimInlines . mconcat <$> manyTill inline newline  titleBlock :: MarkdownParser ()  titleBlock = pandocTitleBlock <|> mmdTitleBlock @@ -215,20 +220,16 @@ pandocTitleBlock = try $ do    guardEnabled Ext_pandoc_title_block    lookAhead (char '%')    title <- option mempty titleLine -  author <- option (return []) authorsLine +  author <- option [] authorsLine    date <- option mempty dateLine    optional blanklines -  let meta' = do title' <- title -                 author' <- author -                 date' <- date -                 return $ -                     (if B.isNull title' then id else B.setMeta "title" title') -                   . (if null author' then id else B.setMeta "author" author') -                   . (if B.isNull date' then id else B.setMeta "date" date') -                   $ nullMeta -  updateState $ \st -> st{ stateMeta' = stateMeta' st <> meta' } - -yamlMetaBlock :: MarkdownParser (F Blocks) +  let meta' = (if B.isNull title then id else B.setMeta "title" title) +              . (if null author then id else B.setMeta "author" author) +              . (if B.isNull date then id else B.setMeta "date" date) +              $ nullMeta +  updateState $ \st -> st{ stateMeta = stateMeta st <> meta' } + +yamlMetaBlock :: MarkdownParser Blocks  yamlMetaBlock = try $ do    guardEnabled Ext_yaml_metadata_block    pos <- getPosition @@ -241,17 +242,17 @@ yamlMetaBlock = try $ do    optional blanklines    opts <- stateOptions <$> getState    meta' <- case Yaml.decodeEither' $ UTF8.fromString rawYaml of -                Right (Yaml.Object hashmap) -> return $ return $ +                Right (Yaml.Object hashmap) -> return $                           H.foldrWithKey (\k v m ->                                if ignorable k                                   then m                                   else B.setMeta (T.unpack k)                                              (yamlToMeta opts v) m)                             nullMeta hashmap -                Right Yaml.Null -> return $ return nullMeta +                Right Yaml.Null -> return nullMeta                  Right _ -> do                              addWarning (Just pos) "YAML header is not an object" -                            return $ return nullMeta +                            return nullMeta                  Left err' -> do                           case err' of                              InvalidYaml (Just YamlParseException{ @@ -270,13 +271,13 @@ yamlMetaBlock = try $ do                              _ -> addWarning (Just pos)                                      $ "Could not parse YAML header: " ++                                          show err' -                         return $ return nullMeta -  updateState $ \st -> st{ stateMeta' = stateMeta' st <> meta' } +                         return nullMeta +  updateState $ \st -> st{ stateMeta = stateMeta st <> meta' }    return mempty  -- ignore fields ending with _  ignorable :: Text -> Bool -ignorable t = (T.pack "_") `T.isSuffixOf` t +ignorable t = T.pack "_" `T.isSuffixOf` t  toMetaValue :: ReaderOptions -> Text -> MetaValue  toMetaValue opts x = @@ -286,7 +287,7 @@ toMetaValue opts x =           | endsWithNewline x -> MetaBlocks [Para xs]           | otherwise         -> MetaInlines xs         Pandoc _ bs           -> MetaBlocks bs -  where endsWithNewline t = (T.pack "\n") `T.isSuffixOf` t +  where endsWithNewline t = T.pack "\n" `T.isSuffixOf` t  yamlToMeta :: ReaderOptions -> Yaml.Value -> MetaValue  yamlToMeta opts (Yaml.String t) = toMetaValue opts t @@ -314,8 +315,8 @@ mmdTitleBlock = try $ do    guardEnabled Ext_mmd_title_block    kvPairs <- many1 kvPair    blanklines -  updateState $ \st -> st{ stateMeta' = stateMeta' st <> -                             return (Meta $ M.fromList kvPairs) } +  updateState $ \st -> st{ stateMeta = stateMeta st <> +                             (Meta $ M.fromList kvPairs) }  kvPair :: MarkdownParser (String, MetaValue)  kvPair = try $ do @@ -335,11 +336,11 @@ parseMarkdown = do    optional titleBlock    blocks <- parseBlocks    st <- getState -  let meta = runF (stateMeta' st) st -  let Pandoc _ bs = B.doc $ runF blocks st +  let meta = stateMeta st +  let Pandoc _ bs = B.doc blocks    return $ Pandoc meta bs -referenceKey :: MarkdownParser (F Blocks) +referenceKey :: MarkdownParser Blocks  referenceKey = try $ do    pos <- getPosition    skipNonindentSpaces @@ -366,7 +367,7 @@ referenceKey = try $ do      Just _  -> addWarning (Just pos) $ "Duplicate link reference `" ++ raw ++ "'"      Nothing -> return ()    updateState $ \s -> s { stateKeys = M.insert key target oldkeys } -  return $ return mempty +  return mempty  referenceTitle :: MarkdownParser String  referenceTitle = try $ do @@ -386,7 +387,7 @@ quotedTitle c = try $ do  -- | PHP Markdown Extra style abbreviation key.  Currently  -- we just skip them, since Pandoc doesn't have an element for  -- an abbreviation. -abbrevKey :: MarkdownParser (F Blocks) +abbrevKey :: MarkdownParser Blocks  abbrevKey = do    guardEnabled Ext_abbreviations    try $ do @@ -395,7 +396,7 @@ abbrevKey = do      char ':'      skipMany (satisfy (/= '\n'))      blanklines -    return $ return mempty +    return mempty  noteMarker :: MarkdownParser String  noteMarker = string "[^" >> many1Till (satisfy $ not . isBlank) (char ']') @@ -413,7 +414,7 @@ rawLines = do    rest <- many rawLine    return $ unlines (first:rest) -noteBlock :: MarkdownParser (F Blocks) +noteBlock :: MarkdownParser Blocks  noteBlock = try $ do    pos <- getPosition    skipNonindentSpaces @@ -425,7 +426,7 @@ noteBlock = try $ do    rest <- many $ try $ blanklines >> indentSpaces >> rawLines    let raw = unlines (first:rest) ++ "\n"    optional blanklines -  parsed <- parseFromString parseBlocks raw +  parsed <- parseFromString (inFootnote parseBlocks) raw    let newnote = (ref, parsed)    oldnotes <- stateNotes' <$> getState    case lookup ref oldnotes of @@ -434,14 +435,22 @@ noteBlock = try $ do    updateState $ \s -> s { stateNotes' = newnote : oldnotes }    return mempty +inFootnote :: MarkdownParser a -> MarkdownParser a +inFootnote p = do +  st <- stateInFootnote <$> getState +  updateState (\s -> s { stateInFootnote = True } ) +  r <- p +  updateState (\s -> s { stateInFootnote = st } ) +  return r +  --  -- parsing blocks  -- -parseBlocks :: MarkdownParser (F Blocks) +parseBlocks :: MarkdownParser Blocks  parseBlocks = mconcat <$> manyTill block eof -block :: MarkdownParser (F Blocks) +block :: MarkdownParser Blocks  block = do    tr <- getOption readerTrace    pos <- getPosition @@ -457,7 +466,7 @@ block = do                 , htmlBlock                 , table                 , codeBlockIndented -               , guardEnabled Ext_latex_macros *> (macro >>= return . return) +               , guardEnabled Ext_latex_macros *> macro                 , rawTeXBlock                 , lineBlock                 , blockQuote @@ -470,29 +479,28 @@ block = do                 , para                 , plain                 ] <?> "block" -  when tr $ do -    st <- getState +  when tr $      trace (printf "line %d: %s" (sourceLine pos) -           (take 60 $ show $ B.toList $ runF res st)) (return ()) +           (take 60 . show . B.toList $ res)) (return ())    return res  --  -- header blocks  -- -header :: MarkdownParser (F Blocks) +header :: MarkdownParser Blocks  header = setextHeader <|> atxHeader <?> "header" -atxHeader :: MarkdownParser (F Blocks) +atxHeader :: MarkdownParser Blocks  atxHeader = try $ do -  level <- many1 (char '#') >>= return . length +  level <- length <$> many1 (char '#')    notFollowedBy $ guardEnabled Ext_fancy_lists >>                    (char '.' <|> char ')') -- this would be a list    skipSpaces -  text <- trimInlinesF . mconcat <$> many (notFollowedBy atxClosing >> inline) +  text <- trimInlines . mconcat <$> many (notFollowedBy atxClosing >> inline)    attr <- atxClosing -  attr' <- registerHeader attr (runF text defaultParserState) -  return $ B.headerWith attr' level <$> text +  attr' <- registerHeader attr text +  return $ B.headerWith attr' level text  atxClosing :: MarkdownParser Attr  atxClosing = try $ do @@ -519,25 +527,25 @@ mmdHeaderIdentifier = do    skipSpaces    return (ident,[],[]) -setextHeader :: MarkdownParser (F Blocks) +setextHeader :: MarkdownParser Blocks  setextHeader = try $ do    -- This lookahead prevents us from wasting time parsing Inlines    -- unless necessary -- it gives a significant performance boost.    lookAhead $ anyLine >> many1 (oneOf setextHChars) >> blankline -  text <- trimInlinesF . mconcat <$> many1 (notFollowedBy setextHeaderEnd >> inline) +  text <- trimInlines . mconcat <$> many1 (notFollowedBy setextHeaderEnd >> inline)    attr <- setextHeaderEnd    underlineChar <- oneOf setextHChars    many (char underlineChar)    blanklines -  let level = (fromMaybe 0 $ findIndex (== underlineChar) setextHChars) + 1 -  attr' <- registerHeader attr (runF text defaultParserState) -  return $ B.headerWith attr' level <$> text +  let level = (fromMaybe 0 $ elemIndex underlineChar setextHChars) + 1 +  attr' <- registerHeader attr text +  return $ B.headerWith attr' level text  --  -- hrule block  -- -hrule :: Parser [Char] st (F Blocks) +hrule :: Monad m => ParserT [Char] st m Blocks  hrule = try $ do    skipSpaces    start <- satisfy isHruleChar @@ -545,24 +553,24 @@ hrule = try $ do    skipMany (spaceChar <|> char start)    newline    optional blanklines -  return $ return B.horizontalRule +  return B.horizontalRule  --  -- code blocks  --  indentedLine :: MarkdownParser String -indentedLine = indentSpaces >> anyLine >>= return . (++ "\n") +indentedLine = indentSpaces >> ((++ "\n") <$> anyLine) -blockDelimiter :: (Char -> Bool) +blockDelimiter :: Monad m +               => (Char -> Bool)                 -> Maybe Int -               -> Parser [Char] st Int +               -> ParserT [Char] st m Int  blockDelimiter f len = try $ do    c <- lookAhead (satisfy f)    case len of        Just l  -> count l (char c) >> many (char c) >> return l -      Nothing -> count 3 (char c) >> many (char c) >>= -                 return . (+ 3) . length +      Nothing -> count 3 (char c) >> ((+ 3) . length <$> many (char c))  attributes :: MarkdownParser Attr  attributes = try $ do @@ -607,7 +615,7 @@ specialAttr = do    char '-'    return $ \(id',cs,kvs) -> (id',cs ++ ["unnumbered"],kvs) -codeBlockFenced :: MarkdownParser (F Blocks) +codeBlockFenced :: MarkdownParser Blocks  codeBlockFenced = try $ do    c <- try (guardEnabled Ext_fenced_code_blocks >> lookAhead (char '~'))       <|> (guardEnabled Ext_backtick_code_blocks >> lookAhead (char '`')) @@ -619,7 +627,7 @@ codeBlockFenced = try $ do    blankline    contents <- manyTill anyLine (blockDelimiter (== c) (Just size))    blanklines -  return $ return $ B.codeBlockWith attr $ intercalate "\n" contents +  return $ B.codeBlockWith attr $ intercalate "\n" contents  -- correctly handle github language identifiers  toLanguageId :: String -> String @@ -628,7 +636,7 @@ toLanguageId = map toLower . go          go "objective-c" = "objectivec"          go x = x -codeBlockIndented :: MarkdownParser (F Blocks) +codeBlockIndented :: MarkdownParser Blocks  codeBlockIndented = do    contents <- many1 (indentedLine <|>                       try (do b <- blanklines @@ -636,15 +644,15 @@ codeBlockIndented = do                               return $ b ++ l))    optional blanklines    classes <- getOption readerIndentedCodeClasses -  return $ return $ B.codeBlockWith ("", classes, []) $ +  return $ B.codeBlockWith ("", classes, []) $             stripTrailingNewlines $ concat contents -lhsCodeBlock :: MarkdownParser (F Blocks) +lhsCodeBlock :: MarkdownParser Blocks  lhsCodeBlock = do    guardEnabled Ext_literate_haskell -  (return . B.codeBlockWith ("",["sourceCode","literate","haskell"],[]) <$> +  (B.codeBlockWith ("",["sourceCode","literate","haskell"],[]) <$>            (lhsCodeBlockBird <|> lhsCodeBlockLaTeX)) -    <|> (return . B.codeBlockWith ("",["sourceCode","haskell"],[]) <$> +    <|> (B.codeBlockWith ("",["sourceCode","haskell"],[]) <$>            lhsCodeBlockInverseBird)  lhsCodeBlockLaTeX :: MarkdownParser String @@ -673,7 +681,7 @@ lhsCodeBlockBirdWith c = try $ do    blanklines    return $ intercalate "\n" lns' -birdTrackLine :: Char -> Parser [Char] st String +birdTrackLine :: Monad m => Char -> ParserT [Char] st m String  birdTrackLine c = try $ do    char c    -- allow html tags on left margin: @@ -701,12 +709,12 @@ emailBlockQuote = try $ do    optional blanklines    return raw -blockQuote :: MarkdownParser (F Blocks) +blockQuote :: MarkdownParser Blocks  blockQuote = do    raw <- emailBlockQuote    -- parse the extracted block, which may contain various block elements: -  contents <- parseFromString parseBlocks $ (intercalate "\n" raw) ++ "\n\n" -  return $ B.blockQuote <$> contents +  contents <- parseFromString parseBlocks $ intercalate "\n" raw ++ "\n\n" +  return $ B.blockQuote contents  --  -- list blocks @@ -749,7 +757,7 @@ anyOrderedListStart = try $ do    return res  listStart :: MarkdownParser () -listStart = bulletListStart <|> (anyOrderedListStart >> return ()) +listStart = bulletListStart <|> void anyOrderedListStart  listLine :: MarkdownParser String  listLine = try $ do @@ -804,7 +812,7 @@ listContinuationLine = try $ do    return $ result ++ "\n"  listItem :: MarkdownParser a -         -> MarkdownParser (F Blocks) +         -> MarkdownParser Blocks  listItem start = try $ do    first <- rawListItem start    continuations <- many listContinuation @@ -820,14 +828,14 @@ listItem start = try $ do    updateState (\st -> st {stateParserContext = oldContext})    return contents -orderedList :: MarkdownParser (F Blocks) +orderedList :: MarkdownParser Blocks  orderedList = try $ do    (start, style, delim) <- lookAhead anyOrderedListStart    unless (style `elem` [DefaultStyle, Decimal, Example] &&            delim `elem` [DefaultDelim, Period]) $      guardEnabled Ext_fancy_lists    when (style == Example) $ guardEnabled Ext_example_lists -  items <- fmap sequence $ many1 $ listItem +  items <- many1 $ listItem                   ( try $ do                       optional newline -- if preceded by Plain block in a list                       startpos <- sourceColumn <$> getPosition @@ -839,12 +847,12 @@ orderedList = try $ do                       atMostSpaces (tabStop - (endpos - startpos))                       return res )    start' <- option 1 $ guardEnabled Ext_startnum >> return start -  return $ B.orderedListWith (start', style, delim) <$> fmap compactify' items +  return $ B.orderedListWith (start', style, delim) (compactify' items) -bulletList :: MarkdownParser (F Blocks) +bulletList :: MarkdownParser Blocks  bulletList = do -  items <- fmap sequence $ many1 $ listItem  bulletListStart -  return $ B.bulletList <$> fmap compactify' items +  items <- many1 $ listItem  bulletListStart +  return $ B.bulletList (compactify' items)  -- definition lists @@ -859,14 +867,14 @@ defListMarker = do       else mzero    return () -definitionListItem :: Bool -> MarkdownParser (F (Inlines, [Blocks])) +definitionListItem :: Bool -> MarkdownParser (Inlines, [Blocks])  definitionListItem compact = try $ do    rawLine' <- anyLine    raw <- many1 $ defRawBlock compact -  term <- parseFromString (trimInlinesF . mconcat <$> many inline) rawLine' +  term <- parseFromString (trimInlines . mconcat <$> many inline) rawLine'    contents <- mapM (parseFromString parseBlocks) raw    optional blanklines -  return $ liftM2 (,) term (sequence contents) +  return (term, contents)  defRawBlock :: Bool -> MarkdownParser String  defRawBlock compact = try $ do @@ -889,32 +897,32 @@ defRawBlock compact = try $ do    return $ trimr (firstline ++ "\n" ++ unlines rawlines ++ cont) ++              if hasBlank || not (null cont) then "\n\n" else "" -definitionList :: MarkdownParser (F Blocks) +definitionList :: MarkdownParser Blocks  definitionList = try $ do    lookAhead (anyLine >> optional blankline >> defListMarker)    compactDefinitionList <|> normalDefinitionList -compactDefinitionList :: MarkdownParser (F Blocks) +compactDefinitionList :: MarkdownParser Blocks  compactDefinitionList = do    guardEnabled Ext_compact_definition_lists -  items <- fmap sequence $ many1 $ definitionListItem True -  return $ B.definitionList <$> fmap compactify'DL items +  items <-  many1 $ definitionListItem True +  return $ B.definitionList (compactify'DL items) -normalDefinitionList :: MarkdownParser (F Blocks) +normalDefinitionList :: MarkdownParser Blocks  normalDefinitionList = do    guardEnabled Ext_definition_lists -  items <- fmap sequence $ many1 $ definitionListItem False -  return $ B.definitionList <$> items +  items <-  many1 $ definitionListItem False +  return $ B.definitionList items  --  -- paragraph block  -- -para :: MarkdownParser (F Blocks) +para :: MarkdownParser Blocks  para = try $ do    exts <- getOption readerExtensions -  result <- trimInlinesF . mconcat <$> many1 inline -  option (B.plain <$> result) +  result <- trimInlines . mconcat <$> many1 inline +  option (B.plain result)      $ try $ do              newline              (blanklines >> return mempty) @@ -931,18 +939,17 @@ para = try $ do                            Just "div" -> () <$                                         lookAhead (htmlTag (~== TagClose "div"))                            _          -> mzero -            return $ do -              result' <- result -              case B.toList result' of +            return $ +              case B.toList result of                     [Image alt (src,tit)]                       | Ext_implicit_figures `Set.member` exts ->                          -- the fig: at beginning of title indicates a figure -                        return $ B.para $ B.singleton +                        B.para $ B.singleton                                 $ Image alt (src,'f':'i':'g':':':tit) -                   _ -> return $ B.para result' +                   _ -> B.para result -plain :: MarkdownParser (F Blocks) -plain = fmap B.plain . trimInlinesF . mconcat <$> many1 inline +plain :: MarkdownParser Blocks +plain = B.plain . trimInlines . mconcat <$> many1 inline  --  -- raw html @@ -953,13 +960,13 @@ htmlElement = rawVerbatimBlock            <|> strictHtmlBlock            <|> liftM snd (htmlTag isBlockTag) -htmlBlock :: MarkdownParser (F Blocks) +htmlBlock :: MarkdownParser Blocks  htmlBlock = do    guardEnabled Ext_raw_html    try (do        (TagOpen t attrs) <- lookAhead $ fst <$> htmlTag isBlockTag        (guard (t `elem` ["pre","style","script"]) >> -          (return . B.rawBlock "html") <$> rawVerbatimBlock) +          B.rawBlock "html" <$> rawVerbatimBlock)          <|> (do guardEnabled Ext_markdown_attribute                  oldMarkdownAttribute <- stateMarkdownAttribute <$> getState                  markdownAttribute <- @@ -978,35 +985,35 @@ htmlBlock = do          <|> (guardEnabled Ext_markdown_in_html_blocks >> rawHtmlBlocks))      <|> htmlBlock' -htmlBlock' :: MarkdownParser (F Blocks) +htmlBlock' :: MarkdownParser Blocks  htmlBlock' = try $ do      first <- htmlElement      skipMany spaceChar      optional blanklines -    return $ return $ B.rawBlock "html" first +    return $ B.rawBlock "html" first  strictHtmlBlock :: MarkdownParser String  strictHtmlBlock = htmlInBalanced (not . isInlineTag)  rawVerbatimBlock :: MarkdownParser String  rawVerbatimBlock = try $ do -  (TagOpen tag _, open) <- htmlTag (tagOpen (flip elem -                                                  ["pre", "style", "script"]) -                              (const True)) +  (TagOpen tag _, open) <- +    htmlTag (tagOpen (`elem` ["pre", "style", "script"]) +            (const True))    contents <- manyTill anyChar (htmlTag (~== TagClose tag))    return $ open ++ contents ++ renderTags' [TagClose tag] -rawTeXBlock :: MarkdownParser (F Blocks) +rawTeXBlock :: MarkdownParser Blocks  rawTeXBlock = do    guardEnabled Ext_raw_tex    result <- (B.rawBlock "latex" . concat <$> -                  rawLaTeXBlock `sepEndBy1` blankline) +                  generalize rawLaTeXBlock `sepEndBy1` blankline)          <|> (B.rawBlock "context" . concat <$>                    rawConTeXtEnvironment `sepEndBy1` blankline)    spaces -  return $ return result +  return result -rawHtmlBlocks :: MarkdownParser (F Blocks) +rawHtmlBlocks :: MarkdownParser Blocks  rawHtmlBlocks = do    (TagOpen tagtype _, raw) <- htmlTag isBlockTag    -- try to find closing tag @@ -1018,10 +1025,10 @@ rawHtmlBlocks = do    contents <- mconcat <$> many (notFollowedBy' closer >> block)    result <-      (closer >>= \(_, rawcloser) -> return ( -                return (B.rawBlock "html" $ stripMarkdownAttribute raw) <> +                (B.rawBlock "html" $ stripMarkdownAttribute raw) <>                  contents <> -                return (B.rawBlock "html" rawcloser))) -      <|> return (return (B.rawBlock "html" raw) <> contents) +                (B.rawBlock "html" rawcloser))) +      <|> return (B.rawBlock "html" raw <> contents)    updateState $ \st -> st{ stateInHtmlBlock = oldInHtmlBlock }    return result @@ -1036,12 +1043,12 @@ stripMarkdownAttribute s = renderTags' $ map filterAttrib $ parseTags s  -- line block  -- -lineBlock :: MarkdownParser (F Blocks) +lineBlock :: MarkdownParser Blocks  lineBlock = try $ do    guardEnabled Ext_line_blocks    lines' <- lineBlockLines >>= -            mapM (parseFromString (trimInlinesF . mconcat <$> many inline)) -  return $ B.para <$> (mconcat $ intersperse (return B.linebreak) lines') +            mapM (parseFromString (trimInlines . mconcat <$> many inline)) +  return $ B.para (mconcat $ intersperse B.linebreak lines')  --  -- Tables @@ -1049,17 +1056,17 @@ lineBlock = try $ do  -- Parse a dashed line with optional trailing spaces; return its length  -- and the length including trailing space. -dashedLine :: Char -           -> Parser [Char] st (Int, Int) +dashedLine :: Monad m => Char +           -> ParserT [Char] st m (Int, Int)  dashedLine ch = do    dashes <- many1 (char ch)    sp     <- many spaceChar -  return $ (length dashes, length $ dashes ++ sp) +  return (length dashes, length $ dashes ++ sp)  -- Parse a table header with dashed lines of '-' preceded by  -- one (or zero) line of text.  simpleTableHeader :: Bool  -- ^ Headerless table -                  -> MarkdownParser (F [Blocks], [Alignment], [Int]) +                  -> MarkdownParser ([Blocks], [Alignment], [Int])  simpleTableHeader headless = try $ do    rawContent  <- if headless                      then return "" @@ -1078,9 +1085,8 @@ simpleTableHeader headless = try $ do    let rawHeads' = if headless                       then replicate (length dashes) ""                       else rawHeads -  heads <- fmap sequence -           $ mapM (parseFromString (mconcat <$> many plain)) -           $ map trim rawHeads' +  heads <- +           mapM (parseFromString (mconcat <$> many plain) . trim) rawHeads'    return (heads, aligns, indices)  -- Returns an alignment type for a table, based on a list of strings @@ -1121,30 +1127,30 @@ rawTableLine indices = do  -- Parse a table line and return a list of lists of blocks (columns).  tableLine :: [Int] -          -> MarkdownParser (F [Blocks]) +          -> MarkdownParser [Blocks]  tableLine indices = rawTableLine indices >>= -  fmap sequence . mapM (parseFromString (mconcat <$> many plain)) +   mapM (parseFromString (mconcat <$> many plain))  -- Parse a multiline table row and return a list of blocks (columns).  multilineRow :: [Int] -             -> MarkdownParser (F [Blocks]) +             -> MarkdownParser [Blocks]  multilineRow indices = do    colLines <- many1 (rawTableLine indices)    let cols = map unlines $ transpose colLines -  fmap sequence $ mapM (parseFromString (mconcat <$> many plain)) cols +  mapM (parseFromString (mconcat <$> many plain)) cols  -- Parses a table caption:  inlines beginning with 'Table:'  -- and followed by blank lines. -tableCaption :: MarkdownParser (F Inlines) +tableCaption :: MarkdownParser Inlines  tableCaption = try $ do    guardEnabled Ext_table_captions    skipNonindentSpaces    string ":" <|> string "Table:" -  trimInlinesF . mconcat <$> many1 inline <* blanklines +  trimInlines . mconcat <$> many1 inline <* blanklines  -- Parse a simple table with '---' header and one line per row.  simpleTable :: Bool  -- ^ Headerless table -            -> MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) +            -> MarkdownParser ([Alignment], [Double], [Blocks], [[Blocks]])  simpleTable headless = do    (aligns, _widths, heads', lines') <-         tableWith (simpleTableHeader headless) tableLine @@ -1158,12 +1164,12 @@ simpleTable headless = do  -- which may be multiline, separated by blank lines, and  -- ending with a footer (dashed line followed by blank line).  multilineTable :: Bool -- ^ Headerless table -               -> MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) +               -> MarkdownParser ([Alignment], [Double], [Blocks], [[Blocks]])  multilineTable headless =    tableWith (multilineTableHeader headless) multilineRow blanklines tableFooter  multilineTableHeader :: Bool -- ^ Headerless table -                     -> MarkdownParser (F [Blocks], [Alignment], [Int]) +                     -> MarkdownParser ([Blocks], [Alignment], [Int])  multilineTableHeader headless = try $ do    unless headless $       tableSep >> notFollowedBy blankline @@ -1185,7 +1191,7 @@ multilineTableHeader headless = try $ do    let rawHeads = if headless                      then replicate (length dashes) ""                      else map (unlines . map trim) rawHeadsList -  heads <- fmap sequence $ +  heads <-             mapM (parseFromString (mconcat <$> many plain)) $               map trim rawHeads    return (heads, aligns, indices) @@ -1195,7 +1201,7 @@ multilineTableHeader headless = try $ do  -- which may be grid, separated by blank lines, and  -- ending with a footer (dashed line followed by blank line).  gridTable :: Bool -- ^ Headerless table -          -> MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) +          -> MarkdownParser ([Alignment], [Double], [Blocks], [[Blocks]])  gridTable headless =    tableWith (gridTableHeader headless) gridTableRow              (gridTableSep '-') gridTableFooter @@ -1204,13 +1210,13 @@ gridTableSplitLine :: [Int] -> String -> [String]  gridTableSplitLine indices line = map removeFinalBar $ tail $    splitStringByIndices (init indices) $ trimr line -gridPart :: Char -> Parser [Char] st (Int, Int) +gridPart :: Monad m => Char -> ParserT [Char] st m (Int, Int)  gridPart ch = do    dashes <- many1 (char ch)    char '+'    return (length dashes, length dashes + 1) -gridDashedLines :: Char -> Parser [Char] st [(Int,Int)] +gridDashedLines :: Monad m => Char -> ParserT [Char] st m [(Int,Int)]  gridDashedLines ch = try $ char '+' >> many1 (gridPart ch) <* blankline  removeFinalBar :: String -> String @@ -1223,7 +1229,7 @@ gridTableSep ch = try $ gridDashedLines ch >> return '\n'  -- | Parse header for a grid table.  gridTableHeader :: Bool -- ^ Headerless table -                -> MarkdownParser (F [Blocks], [Alignment], [Int]) +                -> MarkdownParser ([Blocks], [Alignment], [Int])  gridTableHeader headless = try $ do    optional blanklines    dashes <- gridDashedLines '-' @@ -1232,9 +1238,7 @@ gridTableHeader headless = try $ do                      else many1                           (notFollowedBy (gridTableSep '=') >> char '|' >>                             many1Till anyChar newline) -  if headless -     then return () -     else gridTableSep '=' >> return () +  unless headless (void $ gridTableSep '=')    let lines'   = map snd dashes    let indices  = scanl (+) 0 lines'    let aligns   = replicate (length lines') AlignDefault @@ -1243,7 +1247,7 @@ gridTableHeader headless = try $ do                      then replicate (length dashes) ""                      else map (unlines . map trim) $ transpose                         $ map (gridTableSplitLine indices) rawContent -  heads <- fmap sequence $ mapM (parseFromString parseBlocks . trim) rawHeads +  heads <-  mapM (parseFromString parseBlocks . trim) rawHeads    return (heads, aligns, indices)  gridTableRawLine :: [Int] -> MarkdownParser [String] @@ -1254,12 +1258,12 @@ gridTableRawLine indices = do  -- | Parse row of grid table.  gridTableRow :: [Int] -             -> MarkdownParser (F [Blocks]) +             -> MarkdownParser [Blocks]  gridTableRow indices = do    colLines <- many1 (gridTableRawLine indices)    let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $                 transpose colLines -  fmap compactify' <$> fmap sequence (mapM (parseFromString parseBlocks) cols) +  compactify' <$>  mapM (parseFromString parseBlocks) cols  removeOneLeadingSpace :: [String] -> [String]  removeOneLeadingSpace xs = @@ -1285,14 +1289,12 @@ pipeBreak = try $ do    blankline    return (first:rest) -pipeTable :: MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) +pipeTable :: MarkdownParser ([Alignment], [Double], [Blocks], [[Blocks]])  pipeTable = try $ do -  (heads,aligns) <- pipeTableRow >>= \row -> -                    pipeBreak >>= \als -> -                    return (row, als) -  lines' <- sequence <$> many1 pipeTableRow +  (heads,aligns) <- (,) <$> pipeTableRow <*> pipeBreak +  lines' <-  many1 pipeTableRow    let widths = replicate (length aligns) 0.0 -  return $ (aligns, widths, heads, lines') +  return (aligns, widths, heads, lines')  sepPipe :: MarkdownParser ()  sepPipe = try $ do @@ -1300,7 +1302,7 @@ sepPipe = try $ do    notFollowedBy blankline  -- parse a row, also returning probable alignments for org-table cells -pipeTableRow :: MarkdownParser (F [Blocks]) +pipeTableRow :: MarkdownParser [Blocks]  pipeTableRow = do    nonindentSpaces    openPipe <- (True <$ char '|') <|> return False @@ -1312,16 +1314,14 @@ pipeTableRow = do    guard $ not (null rest && not openPipe)    optional (char '|')    blankline -  let cells  = sequence (first:rest) -  return $ do -    cells' <- cells -    return $ map -        (\ils -> +  let cells  = first:rest +  return $ +    map (\ils ->             case trimInlines ils of                   ils' | B.isNull ils' -> mempty -                      | otherwise   -> B.plain $ ils') cells' +                      | otherwise   -> B.plain ils') cells -pipeTableHeaderPart :: Parser [Char] st Alignment +pipeTableHeaderPart :: Monad m => ParserT [Char] st m Alignment  pipeTableHeaderPart = try $ do    skipMany spaceChar    left <- optionMaybe (char ':') @@ -1336,7 +1336,7 @@ pipeTableHeaderPart = try $ do        (Just _,Just _)   -> AlignCenter  -- Succeed only if current line contains a pipe. -scanForPipe :: Parser [Char] st () +scanForPipe :: Monad m => ParserT [Char] st m ()  scanForPipe = do    inp <- getInput    case break (\c -> c == '\n' || c == '|') inp of @@ -1346,22 +1346,22 @@ scanForPipe = do  -- | Parse a table using 'headerParser', 'rowParser',  -- 'lineParser', and 'footerParser'.  Variant of the version in  -- Text.Pandoc.Parsing. -tableWith :: MarkdownParser (F [Blocks], [Alignment], [Int]) -          -> ([Int] -> MarkdownParser (F [Blocks])) +tableWith :: MarkdownParser ([Blocks], [Alignment], [Int]) +          -> ([Int] -> MarkdownParser [Blocks])            -> MarkdownParser sep            -> MarkdownParser end -          -> MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) +          -> MarkdownParser ([Alignment], [Double], [Blocks], [[Blocks]])  tableWith headerParser rowParser lineParser footerParser = try $ do      (heads, aligns, indices) <- headerParser -    lines' <- fmap sequence $ rowParser indices `sepEndBy1` lineParser +    lines' <-  rowParser indices `sepEndBy1` lineParser      footerParser      numColumns <- getOption readerColumns -    let widths = if (indices == []) -                    then replicate (length aligns) 0.0 -                    else widthsFromIndices numColumns indices -    return $ (aligns, widths, heads, lines') +    let widths = case indices of +                  [] -> replicate (length aligns) 0.0 +                  _  -> widthsFromIndices numColumns indices +    return (aligns, widths, heads, lines') -table :: MarkdownParser (F Blocks) +table :: MarkdownParser Blocks  table = try $ do    frontCaption <- option Nothing (Just <$> tableCaption)    (aligns, widths, heads, lns) <- @@ -1376,19 +1376,15 @@ table = try $ do                  (gridTable False <|> gridTable True)) <?> "table"    optional blanklines    caption <- case frontCaption of -                  Nothing  -> option (return mempty) tableCaption +                  Nothing  -> option mempty tableCaption                    Just c   -> return c -  return $ do -    caption' <- caption -    heads' <- heads -    lns' <- lns -    return $ B.table caption' (zip aligns widths) heads' lns' +  return $ B.table caption (zip aligns widths) heads lns  --  -- inline  -- -inline :: MarkdownParser (F Inlines) +inline :: MarkdownParser Inlines  inline = choice [ whitespace                  , bareURL                  , str @@ -1411,7 +1407,7 @@ inline = choice [ whitespace                  , rawLaTeXInline'                  , exampleRef                  , smart -                , return . B.singleton <$> charRef +                , B.singleton <$> charRef                  , symbol                  , ltSign                  ] <?> "inline" @@ -1422,43 +1418,42 @@ escapedChar' = try $ do    (guardEnabled Ext_all_symbols_escapable >> satisfy (not . isAlphaNum))       <|> oneOf "\\`*_{}[]()>#+-.!~\"" -escapedChar :: MarkdownParser (F Inlines) +escapedChar :: MarkdownParser Inlines  escapedChar = do    result <- escapedChar'    case result of -       ' '   -> return $ return $ B.str "\160" -- "\ " is a nonbreaking space +       ' '   -> return $ B.str "\160" -- "\ " is a nonbreaking space         '\n'  -> guardEnabled Ext_escaped_line_breaks >> -                return (return B.linebreak)  -- "\[newline]" is a linebreak -       _     -> return $ return $ B.str [result] +                return B.linebreak  -- "\[newline]" is a linebreak +       _     -> return $ B.str [result] -ltSign :: MarkdownParser (F Inlines) +ltSign :: MarkdownParser Inlines  ltSign = do    guardDisabled Ext_raw_html      <|> (notFollowedByHtmlCloser >> notFollowedBy' (htmlTag isBlockTag))    char '<' -  return $ return $ B.str "<" +  return $ B.str "<" -exampleRef :: MarkdownParser (F Inlines) +exampleRef :: MarkdownParser Inlines  exampleRef = try $ do    guardEnabled Ext_example_lists    char '@'    lab <- many1 (alphaNum <|> oneOf "-_") -  return $ do -    st <- askF -    return $ case M.lookup lab (stateExamples st) of -                  Just n    -> B.str (show n) -                  Nothing   -> B.str ('@':lab) +  st <- ask +  return $ case M.lookup lab (stateExamples st) of +                Just n    -> B.str (show n) +                Nothing   -> B.str ('@':lab) -symbol :: MarkdownParser (F Inlines) +symbol :: MarkdownParser Inlines  symbol = do    result <- noneOf "<\\\n\t "           <|> try (do lookAhead $ char '\\'                       notFollowedBy' (() <$ rawTeXBlock)                       char '\\') -  return $ return $ B.str [result] +  return $ B.str [result]  -- parses inline code, between n `s and n `s -code :: MarkdownParser (F Inlines) +code :: MarkdownParser Inlines  code = try $ do    starts <- many1 (char '`')    skipSpaces @@ -1468,16 +1463,16 @@ code = try $ do                        notFollowedBy (char '`')))    attr <- option ([],[],[]) (try $ guardEnabled Ext_inline_code_attributes >>                                     optional whitespace >> attributes) -  return $ return $ B.codeWith attr $ trim $ concat result +  return $ B.codeWith attr $ trim $ concat result -math :: MarkdownParser (F Inlines) -math =  (return . B.displayMath <$> (mathDisplay >>= applyMacros')) -     <|> (return . B.math <$> (mathInline >>= applyMacros')) +math :: MarkdownParser Inlines +math =  (B.displayMath <$> (mathDisplay >>= applyMacros')) +     <|> (B.math <$> (mathInline >>= applyMacros'))  -- Parses material enclosed in *s, **s, _s, or __s.  -- Designed to avoid backtracking.  enclosure :: Char -          -> MarkdownParser (F Inlines) +          -> MarkdownParser Inlines  enclosure c = do    -- we can't start an enclosure with _ if after a string and    -- the intraword_underscores extension is enabled: @@ -1485,13 +1480,13 @@ enclosure c = do      <|> guard (c == '*')      <|> (guard =<< notAfterString)    cs <- many1 (char c) -  (return (B.str cs) <>) <$> whitespace -    <|> do +  (B.str cs <>) <$> whitespace +    <|>          case length cs of               3  -> three c               2  -> two   c mempty               1  -> one   c mempty -             _  -> return (return $ B.str cs) +             _  -> return $ B.str cs  ender :: Char -> Int -> MarkdownParser ()  ender c n = try $ do @@ -1504,74 +1499,74 @@ ender c n = try $ do  -- If one c, emit emph and then parse two.  -- If two cs, emit strong and then parse one.  -- Otherwise, emit ccc then the results. -three :: Char -> MarkdownParser (F Inlines) +three :: Char -> MarkdownParser Inlines  three c = do    contents <- mconcat <$> many (notFollowedBy (ender c 1) >> inline) -  (ender c 3 >> return ((B.strong . B.emph) <$> contents)) -    <|> (ender c 2 >> one c (B.strong <$> contents)) -    <|> (ender c 1 >> two c (B.emph <$> contents)) -    <|> return (return (B.str [c,c,c]) <> contents) +  (ender c 3 >> return ((B.strong . B.emph) contents)) +    <|> (ender c 2 >> one c (B.strong contents)) +    <|> (ender c 1 >> two c (B.emph contents)) +    <|> return (B.str [c,c,c] <> contents)  -- Parse inlines til you hit two c's, and emit strong.  -- If you never do hit two cs, emit ** plus inlines parsed. -two :: Char -> F Inlines -> MarkdownParser (F Inlines) +two :: Char -> Inlines -> MarkdownParser Inlines  two c prefix' = do    contents <- mconcat <$> many (try $ notFollowedBy (ender c 2) >> inline) -  (ender c 2 >> return (B.strong <$> (prefix' <> contents))) -    <|> return (return (B.str [c,c]) <> (prefix' <> contents)) +  (ender c 2 >> return (B.strong (prefix' <> contents))) +    <|> return (B.str [c,c] <> (prefix' <> contents))  -- Parse inlines til you hit a c, and emit emph.  -- If you never hit a c, emit * plus inlines parsed. -one :: Char -> F Inlines -> MarkdownParser (F Inlines) +one :: Char -> Inlines -> MarkdownParser Inlines  one c prefix' = do    contents <- mconcat <$> many (  (notFollowedBy (ender c 1) >> inline)                             <|> try (string [c,c] >>                                      notFollowedBy (ender c 1) >>                                      two c mempty) ) -  (ender c 1 >> return (B.emph <$> (prefix' <> contents))) -    <|> return (return (B.str [c]) <> (prefix' <> contents)) +  (ender c 1 >> return (B.emph (prefix' <> contents))) +    <|> return (B.str [c] <> (prefix' <> contents)) -strongOrEmph :: MarkdownParser (F Inlines) +strongOrEmph :: MarkdownParser Inlines  strongOrEmph =  enclosure '*' <|> enclosure '_' --- | Parses a list of inlines between start and end delimiters. +-- | Parses a list oInlines between start and end delimiters.  inlinesBetween :: (Show b)                 => MarkdownParser a                 -> MarkdownParser b -               -> MarkdownParser (F Inlines) +               -> MarkdownParser Inlines  inlinesBetween start end = -  (trimInlinesF . mconcat) <$> try (start >> many1Till inner end) +  (trimInlines . mconcat) <$> try (start >> many1Till inner end)      where inner      = innerSpace <|> (notFollowedBy' (() <$ whitespace) >> inline)            innerSpace = try $ whitespace <* notFollowedBy' end -strikeout :: MarkdownParser (F Inlines) -strikeout = fmap B.strikeout <$> +strikeout :: MarkdownParser Inlines +strikeout = B.strikeout <$>   (guardEnabled Ext_strikeout >> inlinesBetween strikeStart strikeEnd)      where strikeStart = string "~~" >> lookAhead nonspaceChar                          >> notFollowedBy (char '~')            strikeEnd   = try $ string "~~" -superscript :: MarkdownParser (F Inlines) -superscript = fmap B.superscript <$> try (do +superscript :: MarkdownParser Inlines +superscript = B.superscript <$> try (do    guardEnabled Ext_superscript    char '^'    mconcat <$> many1Till (notFollowedBy spaceChar >> inline) (char '^')) -subscript :: MarkdownParser (F Inlines) -subscript = fmap B.subscript <$> try (do +subscript :: MarkdownParser Inlines +subscript = B.subscript <$> try (do    guardEnabled Ext_subscript    char '~'    mconcat <$> many1Till (notFollowedBy spaceChar >> inline) (char '~')) -whitespace :: MarkdownParser (F Inlines) -whitespace = spaceChar >> return <$> (lb <|> regsp) <?> "whitespace" +whitespace :: MarkdownParser Inlines +whitespace = spaceChar >> (lb <|> regsp) <?> "whitespace"    where lb = spaceChar >> skipMany spaceChar >> option B.space (endline >> return B.linebreak)          regsp = skipMany spaceChar >> return B.space -nonEndline :: Parser [Char] st Char +nonEndline :: Monad m => ParserT [Char] st m Char  nonEndline = satisfy (/='\n') -str :: MarkdownParser (F Inlines) +str :: MarkdownParser Inlines  str = do    result <- many1 alphaNum    updateLastStrPos @@ -1579,14 +1574,14 @@ str = do    isSmart <- getOption readerSmart    if isSmart       then case likelyAbbrev result of -               []        -> return $ return $ B.str result +               []        -> return $ B.str result                 xs        -> choice (map (\x ->                                 try (string x >> oneOf " \n" >>                                      lookAhead alphaNum >> -                                    return (return $ B.str -                                                  $ result ++ spacesToNbr x ++ "\160"))) xs) -                           <|> (return $ return $ B.str result) -     else return $ return $ B.str result +                                    return (B.str $ +                                      result ++ spacesToNbr x ++ "\160"))) xs) +                           <|> (return $ B.str result) +     else return $ B.str result  -- | if the string matches the beginning of an abbreviation (before  -- the first period, return strings that would finish the abbreviation. @@ -1601,7 +1596,7 @@ likelyAbbrev x =    in  map snd $ filter (\(y,_) -> y == x) abbrPairs  -- an endline character that can be treated as a space, not a structural break -endline :: MarkdownParser (F Inlines) +endline :: MarkdownParser Inlines  endline = try $ do    newline    notFollowedBy blankline @@ -1614,18 +1609,18 @@ endline = try $ do       notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))    notFollowedByHtmlCloser    (eof >> return mempty) -    <|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak)) +    <|> (guardEnabled Ext_hard_line_breaks >> return B.linebreak)      <|> (guardEnabled Ext_ignore_line_breaks >> return mempty) -    <|> (return $ return B.space) +    <|> return B.space  --  -- links  --  -- a reference label for a link -reference :: MarkdownParser (F Inlines, String) +reference :: MarkdownParser (Inlines, String)  reference = do notFollowedBy' (string "[^")   -- footnote reference -               withRaw $ trimInlinesF <$> inlinesInBalancedBrackets +               withRaw $ trimInlines <$> inlinesInBalancedBrackets  parenthesizedChars :: MarkdownParser [Char]  parenthesizedChars = do @@ -1653,7 +1648,7 @@ source = do  linkTitle :: MarkdownParser String  linkTitle = quotedTitle '"' <|> quotedTitle '\'' -link :: MarkdownParser (F Inlines) +link :: MarkdownParser Inlines  link = try $ do    st <- getState    guard $ stateAllowLinks st @@ -1663,14 +1658,14 @@ link = try $ do    regLink B.link lab <|> referenceLink B.link (lab,raw)  regLink :: (String -> String -> Inlines -> Inlines) -        -> F Inlines -> MarkdownParser (F Inlines) +        -> Inlines -> MarkdownParser Inlines  regLink constructor lab = try $ do    (src, tit) <- source -  return $ constructor src tit <$> lab +  return $ constructor src tit lab  -- a link like [this][ref] or [this][] or [this]  referenceLink :: (String -> String -> Inlines -> Inlines) -              -> (F Inlines, String) -> MarkdownParser (F Inlines) +              -> (Inlines, String) -> MarkdownParser Inlines  referenceLink constructor (lab, raw) = do    sp <- (True <$ lookAhead (char ' ')) <|> return False    (ref,raw') <- option (mempty, "") $ @@ -1684,24 +1679,22 @@ referenceLink constructor (lab, raw) = do    fallback <- parseFromString (mconcat <$> many inline) $ dropBrackets raw    implicitHeaderRefs <- option False $                           True <$ guardEnabled Ext_implicit_header_references -  let makeFallback = do -       parsedRaw' <- parsedRaw -       fallback' <- fallback -       return $ B.str "[" <> fallback' <> B.str "]" <> +  let makeFallback = +                B.str "[" <> fallback <> B.str "]" <>                  (if sp && not (null raw) then B.space else mempty) <> -                parsedRaw' -  return $ do -    keys <- asksF stateKeys -    case M.lookup key keys of -       Nothing        -> do -         headers <- asksF stateHeaders -         ref' <- if labIsRef then lab else ref -         if implicitHeaderRefs -            then case M.lookup ref' headers of -                   Just ident -> constructor ('#':ident) "" <$> lab -                   Nothing    -> makeFallback -            else makeFallback -       Just (src,tit) -> constructor src tit <$> lab +                parsedRaw +  keys <- asks stateKeys +  headers <- asks stateHeaders +  return $ +     case M.lookup key keys of +     Nothing        -> +       let ref' = if labIsRef then lab else ref in +       if implicitHeaderRefs +          then case M.lookup ref' headers of +                 Just ident -> constructor ('#':ident) "" lab +                 Nothing    -> makeFallback +          else makeFallback +     Just (src,tit) -> constructor src tit lab  dropBrackets :: String -> String  dropBrackets = reverse . dropRB . reverse . dropLB @@ -1710,14 +1703,14 @@ dropBrackets = reverse . dropRB . reverse . dropLB          dropLB ('[':xs) = xs          dropLB xs = xs -bareURL :: MarkdownParser (F Inlines) +bareURL :: MarkdownParser Inlines  bareURL = try $ do    guardEnabled Ext_autolink_bare_uris    (orig, src) <- uri <|> emailAddress    notFollowedBy $ try $ spaces >> htmlTag (~== TagClose "a") -  return $ return $ B.link src "" (B.str orig) +  return $ B.link src "" (B.str orig) -autoLink :: MarkdownParser (F Inlines) +autoLink :: MarkdownParser Inlines  autoLink = try $ do    char '<'    (orig, src) <- uri <|> emailAddress @@ -1726,9 +1719,9 @@ autoLink = try $ do    -- final punctuation.  for example:  in `<http://hi---there>`,    -- the URI parser will stop before the dashes.    extra <- fromEntities <$> manyTill nonspaceChar (char '>') -  return $ return $ B.link (src ++ escapeURI extra) "" (B.str $ orig ++ extra) +  return $ B.link (src ++ escapeURI extra) "" (B.str $ orig ++ extra) -image :: MarkdownParser (F Inlines) +image :: MarkdownParser Inlines  image = try $ do    char '!'    (lab,raw) <- reference @@ -1738,38 +1731,33 @@ image = try $ do                                _  -> B.image src    regLink constructor lab <|> referenceLink constructor (lab,raw) -note :: MarkdownParser (F Inlines) +note :: MarkdownParser Inlines  note = try $ do    guardEnabled Ext_footnotes +  (stateInFootnote <$> getState) >>= guard . not    ref <- noteMarker -  return $ do -    notes <- asksF stateNotes' +  notes <- asks stateNotes' +  return $      case lookup ref notes of -        Nothing       -> return $ B.str $ "[^" ++ ref ++ "]" -        Just contents -> do -          st <- askF -          -- process the note in a context that doesn't resolve -          -- notes, to avoid infinite looping with notes inside -          -- notes: -          let contents' = runF contents st{ stateNotes' = [] } -          return $ B.note contents' - -inlineNote :: MarkdownParser (F Inlines) +        Nothing       -> B.str $ "[^" ++ ref ++ "]" +        Just contents -> B.note contents + +inlineNote :: MarkdownParser Inlines  inlineNote = try $ do    guardEnabled Ext_inline_notes    char '^'    contents <- inlinesInBalancedBrackets -  return $ B.note . B.para <$> contents +  return . B.note . B.para $ contents -rawLaTeXInline' :: MarkdownParser (F Inlines) +rawLaTeXInline' :: MarkdownParser Inlines  rawLaTeXInline' = try $ do    guardEnabled Ext_raw_tex    lookAhead $ char '\\' >> notFollowedBy' (string "start") -- context env -  RawInline _ s <- rawLaTeXInline -  return $ return $ B.rawInline "tex" s +  RawInline _ s <- generalize rawLaTeXInline +  return $ B.rawInline "tex" s    -- "tex" because it might be context or latex -rawConTeXtEnvironment :: Parser [Char] st String +rawConTeXtEnvironment :: Monad m => ParserT [Char] st m String  rawConTeXtEnvironment = try $ do    string "\\start"    completion <- inBrackets (letter <|> digit <|> spaceChar) @@ -1778,14 +1766,14 @@ rawConTeXtEnvironment = try $ do                         (try $ string "\\stop" >> string completion)    return $ "\\start" ++ completion ++ concat contents ++ "\\stop" ++ completion -inBrackets :: (Parser [Char] st Char) -> Parser [Char] st String +inBrackets :: Monad m => (ParserT [Char] st m Char) -> ParserT [Char] st m String  inBrackets parser = do    char '['    contents <- many parser    char ']'    return $ "[" ++ contents ++ "]" -spanHtml :: MarkdownParser (F Inlines) +spanHtml :: MarkdownParser Inlines  spanHtml = try $ do    guardEnabled Ext_native_spans    (TagOpen _ attrs, _) <- htmlTag (~== TagOpen "span" []) @@ -1797,10 +1785,10 @@ spanHtml = try $ do         Just s | null ident && null classes &&              map toLower (filter (`notElem` " \t;") s) ==                   "font-variant:small-caps" -         -> return $ B.smallcaps <$> contents -       _ -> return $ B.spanWith (ident, classes, keyvals) <$> contents +         -> return $ B.smallcaps contents +       _ -> return $ B.spanWith (ident, classes, keyvals) contents -divHtml :: MarkdownParser (F Blocks) +divHtml :: MarkdownParser Blocks  divHtml = try $ do    guardEnabled Ext_native_divs    (TagOpen _ attrs, rawtag) <- htmlTag (~== TagOpen "div" []) @@ -1818,11 +1806,11 @@ divHtml = try $ do         let ident = fromMaybe "" $ lookup "id" attrs         let classes = maybe [] words $ lookup "class" attrs         let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"] -       return $ B.divWith (ident, classes, keyvals) <$> contents +       return $ B.divWith (ident, classes, keyvals) contents       else -- avoid backtracing -       return $ return (B.rawBlock "html" (rawtag <> bls)) <> contents +       return $ B.rawBlock "html" (rawtag <> bls) <> contents -rawHtmlInline :: MarkdownParser (F Inlines) +rawHtmlInline :: MarkdownParser Inlines  rawHtmlInline = do    guardEnabled Ext_raw_html    inHtmlBlock <- stateInHtmlBlock <$> getState @@ -1837,19 +1825,17 @@ rawHtmlInline = do                               then (\x -> isInlineTag x &&                                           not (isCloseBlockTag x))                               else not . isTextTag -  return $ return $ B.rawInline "html" result +  return $ B.rawInline "html" result  -- Citations -cite :: MarkdownParser (F Inlines) +cite :: MarkdownParser Inlines  cite = do    guardEnabled Ext_citations -  citations <- textualCite -            <|> do (cs, raw) <- withRaw normalCite -                   return $ (flip B.cite (B.text raw)) <$> cs -  return citations +  textualCite <|> do (cs, raw) <- withRaw normalCite +                     return $ B.cite cs (B.text raw) -textualCite :: MarkdownParser (F Inlines) +textualCite :: MarkdownParser Inlines  textualCite = try $ do    (_, key) <- citeKey    let first = Citation{ citationId      = key @@ -1863,29 +1849,26 @@ textualCite = try $ do    case mbrest of         Just (rest, raw) ->           return $ (flip B.cite (B.text $ '@':key ++ " " ++ raw) . (first:)) -               <$> rest +                    rest         Nothing   ->           (do (cs, raw) <- withRaw $ bareloc first -             return $ (flip B.cite (B.text $ '@':key ++ " " ++ raw)) <$> cs) -         <|> return (do st <- askF -                        return $ case M.lookup key (stateExamples st) of -                                 Just n -> B.str (show n) -                                 _      -> B.cite [first] $ B.str $ '@':key) +             return $ B.cite cs (B.text $ '@':key ++ " " ++ raw)) +         <|> do st <- ask +                return $ case M.lookup key (stateExamples st) of +                              Just n -> B.str (show n) +                              _      -> B.cite [first] $ B.str $ '@':key -bareloc :: Citation -> MarkdownParser (F [Citation]) +bareloc :: Citation -> MarkdownParser [Citation]  bareloc c = try $ do    spnl    char '['    suff <- suffix -  rest <- option (return []) $ try $ char ';' >> citeList +  rest <- option [] $ try $ char ';' >> citeList    spnl    char ']' -  return $ do -    suff' <- suff -    rest' <- rest -    return $ c{ citationSuffix = B.toList suff' } : rest' +  return $ c{ citationSuffix = B.toList suff } : rest -normalCite :: MarkdownParser (F [Citation]) +normalCite :: MarkdownParser [Citation]  normalCite = try $ do    char '['    spnl @@ -1894,60 +1877,57 @@ normalCite = try $ do    char ']'    return citations -suffix :: MarkdownParser (F Inlines) +suffix :: MarkdownParser Inlines  suffix = try $ do    hasSpace <- option False (notFollowedBy nonspaceChar >> return True)    spnl -  rest <- trimInlinesF . mconcat <$> many (notFollowedBy (oneOf ";]") >> inline) +  rest <- trimInlines . mconcat <$> many (notFollowedBy (oneOf ";]") >> inline)    return $ if hasSpace -              then (B.space <>) <$> rest +              then B.space <> rest                else rest -prefix :: MarkdownParser (F Inlines) -prefix = trimInlinesF . mconcat <$> +prefix :: MarkdownParser Inlines +prefix = trimInlines . mconcat <$>    manyTill inline (char ']' <|> liftM (const ']') (lookAhead citeKey)) -citeList :: MarkdownParser (F [Citation]) -citeList = fmap sequence $ sepBy1 citation (try $ char ';' >> spnl) +citeList :: MarkdownParser [Citation] +citeList =  sepBy1 citation (try $ char ';' >> spnl) -citation :: MarkdownParser (F Citation) +citation :: MarkdownParser Citation  citation = try $ do    pref <- prefix    (suppress_author, key) <- citeKey    suff <- suffix -  return $ do -    x <- pref -    y <- suff -    return $ Citation{ citationId      = key -                     , citationPrefix  = B.toList x -                     , citationSuffix  = B.toList y -                     , citationMode    = if suppress_author -                                            then SuppressAuthor -                                            else NormalCitation -                     , citationNoteNum = 0 -                     , citationHash    = 0 -                     } - -smart :: MarkdownParser (F Inlines) +  return Citation{ citationId      = key +                 , citationPrefix  = B.toList pref +                 , citationSuffix  = B.toList suff +                 , citationMode    = if suppress_author +                                        then SuppressAuthor +                                        else NormalCitation +                 , citationNoteNum = 0 +                 , citationHash    = 0 +                 } + +smart :: MarkdownParser Inlines  smart = do    getOption readerSmart >>= guard    doubleQuoted <|> singleQuoted <|> -    choice (map (return <$>) [apostrophe, dash, ellipses]) +    choice [apostrophe, dash, ellipses] -singleQuoted :: MarkdownParser (F Inlines) +singleQuoted :: MarkdownParser Inlines  singleQuoted = try $ do    singleQuoteStart    withQuoteContext InSingleQuote $ -    fmap B.singleQuoted . trimInlinesF . mconcat <$> +    B.singleQuoted . trimInlines . mconcat <$>        many1Till inline singleQuoteEnd  -- doubleQuoted will handle regular double-quoted sections, as well  -- as dialogues with an open double-quote without a close double-quote  -- in the same paragraph. -doubleQuoted :: MarkdownParser (F Inlines) +doubleQuoted :: MarkdownParser Inlines  doubleQuoted = try $ do    doubleQuoteStart    contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) -  (withQuoteContext InDoubleQuote $ doubleQuoteEnd >> return -       (fmap B.doubleQuoted . trimInlinesF $ contents)) -   <|> (return $ return (B.str "\8220") <> contents) +  (withQuoteContext InDoubleQuote doubleQuoteEnd >> return +       (B.doubleQuoted . trimInlines $ contents)) +   <|> return (B.str "\8220" <> contents) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 4a523657c..457db200b 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,6 +1,9 @@  {-# LANGUAGE OverloadedStrings #-}  {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-}  {-  Copyright (C) 2014 Albert Krewinkel <tarleb@moltkeplatz.de> @@ -36,8 +39,7 @@ import           Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..), (<>)  import           Text.Pandoc.Definition  import           Text.Pandoc.Options  import qualified Text.Pandoc.Parsing as P -import           Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF -                                            , newline, orderedListMarker +import           Text.Pandoc.Parsing hiding ( newline, orderedListMarker                                              , parseFromString, blanklines                                              )  import           Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline) @@ -45,36 +47,45 @@ import           Text.Pandoc.Shared (compactify', compactify'DL)  import           Text.TeXMath (readTeX, writePandoc, DisplayType(..))  import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap -import           Control.Applicative ( Applicative, pure +import           Control.Applicative ( pure                                       , (<$>), (<$), (<*>), (<*), (*>) )  import           Control.Arrow (first) -import           Control.Monad (foldM, guard, liftM, liftM2, mplus, mzero, when) -import           Control.Monad.Reader (Reader, runReader, ask, asks, local) +import           Control.Monad (guard, mplus, mzero, when) +import           Control.Monad.Reader (Reader, runReader, asks, local)  import           Data.Char (isAlphaNum, toLower)  import           Data.Default -import           Data.List (intersperse, isPrefixOf, isSuffixOf) +import           Data.List (intersperse, isPrefixOf, isSuffixOf, foldl')  import qualified Data.Map as M  import           Data.Maybe (fromMaybe, isJust) -import           Data.Monoid (Monoid, mconcat, mempty, mappend) +import           Data.Monoid (mconcat, mempty, mappend)  import           Network.HTTP (urlEncode)  -- | Parse org-mode string and return a Pandoc document.  readOrg :: ReaderOptions -- ^ Reader options          -> String        -- ^ String to parse (assuming @'\n'@ line endings)          -> Pandoc -readOrg opts s = flip runReader def $ readWithM parseOrg def{ orgStateOptions = opts } (s ++ "\n\n") +readOrg opts s = runOrg opts s parseOrg -data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext } +data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext +                                     , finalState :: OrgParserState }  type OrgParser = ParserT [Char] OrgParserState (Reader OrgParserLocal) +runOrg :: ReaderOptions -> String -> OrgParser a -> a +runOrg opts inp p = fst res +  where +    imd = readWithM (returnState p) def{ orgStateOptions = opts } (inp ++ "\n\n") +    res = runReader imd def { finalState = s } +    s :: OrgParserState +    s   = snd $ runReader imd (def { finalState = s }) +  parseOrg :: OrgParser Pandoc  parseOrg = do    blocks' <- parseBlocks    st <- getState -  let meta = runF (orgStateMeta' st) st +  let meta = orgStateMeta st    let removeUnwantedBlocks = dropCommentTrees . filter (/= Null) -  return $ Pandoc meta $ removeUnwantedBlocks (B.toList $ runF blocks' st) +  return $ Pandoc meta $ removeUnwantedBlocks (B.toList $ blocks')  -- | Drop COMMENT headers and the document tree below those headers.  dropCommentTrees :: [Block] -> [Block] @@ -104,7 +115,7 @@ isHeaderLevelLowerEq n blk =  -- Parser State for Org  -- -type OrgNoteRecord = (String, F Blocks) +type OrgNoteRecord = (String, Blocks)  type OrgNoteTable = [OrgNoteRecord]  type OrgBlockAttributes = M.Map String String @@ -123,12 +134,11 @@ data OrgParserState = OrgParserState                        , orgStateLastStrPos           :: Maybe SourcePos                        , orgStateLinkFormatters       :: OrgLinkFormatters                        , orgStateMeta                 :: Meta -                      , orgStateMeta'                :: F Meta                        , orgStateNotes'               :: OrgNoteTable                        }  instance Default OrgParserLocal where -  def = OrgParserLocal NoQuote +  def = OrgParserLocal NoQuote def  instance HasReaderOptions OrgParserState where    extractReaderOptions = orgStateOptions @@ -162,13 +172,13 @@ defaultOrgParserState = OrgParserState                          , orgStateLastStrPos = Nothing                          , orgStateLinkFormatters = M.empty                          , orgStateMeta = nullMeta -                        , orgStateMeta' = return nullMeta                          , orgStateNotes' = []                          }  recordAnchorId :: String -> OrgParser ()  recordAnchorId i = updateState $ \s -> -  s{ orgStateAnchorIds = i : (orgStateAnchorIds s) } +  let as = orgStateAnchorIds s in +  s{ orgStateAnchorIds = i : as }  addBlockAttribute :: String -> String -> OrgParser ()  addBlockAttribute key val = updateState $ \s -> @@ -247,30 +257,6 @@ parseFromString parser str' = do  -- Adaptions and specializations of parsing utilities  -- -newtype F a = F { unF :: Reader OrgParserState a -                } deriving (Monad, Applicative, Functor) - -runF :: F a -> OrgParserState -> a -runF = runReader . unF - -askF :: F OrgParserState -askF = F ask - -asksF :: (OrgParserState -> a) -> F a -asksF f = F $ asks f - -instance Monoid a => Monoid (F a) where -  mempty = return mempty -  mappend = liftM2 mappend -  mconcat = fmap mconcat . sequence - -trimInlinesF :: F Inlines -> F Inlines -trimInlinesF = liftM trimInlines - -returnF :: a -> OrgParser (F a) -returnF = return . return - -  -- | Like @Text.Parsec.Char.newline@, but causes additional state changes.  newline :: OrgParser Char  newline = @@ -289,10 +275,10 @@ blanklines =  -- parsing blocks  -- -parseBlocks :: OrgParser (F Blocks) +parseBlocks :: OrgParser Blocks  parseBlocks = mconcat <$> manyTill block eof -block :: OrgParser (F Blocks) +block :: OrgParser Blocks  block = choice [ mempty <$ blanklines                 , optionalAttributes $ choice                   [ orgBlock @@ -303,14 +289,14 @@ block = choice [ mempty <$ blanklines                 , drawer                 , specialLine                 , header -               , return <$> hline +               , hline                 , list                 , latexFragment                 , noteBlock                 , paraOrPlain                 ] <?> "block" -optionalAttributes :: OrgParser (F Blocks) -> OrgParser (F Blocks) +optionalAttributes :: OrgParser Blocks -> OrgParser Blocks  optionalAttributes parser = try $    resetBlockAttributes *> parseBlockAttributes *> parser @@ -330,7 +316,7 @@ parseAndAddAttribute key value = do    let key' = map toLower key    () <$ addBlockAttribute key' value -lookupInlinesAttr :: String -> OrgParser (Maybe (F Inlines)) +lookupInlinesAttr :: String -> OrgParser (Maybe Inlines)  lookupInlinesAttr attr = try $ do    val <- lookupBlockAttribute attr    maybe (return Nothing) @@ -344,20 +330,20 @@ lookupInlinesAttr attr = try $ do  type BlockProperties = (Int, String)  -- (Indentation, Block-Type) -orgBlock :: OrgParser (F Blocks) +orgBlock :: OrgParser Blocks  orgBlock = try $ do    blockProp@(_, blkType) <- blockHeaderStart    ($ blockProp) $      case blkType of        "comment" -> withRaw'   (const mempty) -      "html"    -> withRaw'   (return . (B.rawBlock blkType)) -      "latex"   -> withRaw'   (return . (B.rawBlock blkType)) -      "ascii"   -> withRaw'   (return . (B.rawBlock blkType)) -      "example" -> withRaw'   (return . exampleCode) -      "quote"   -> withParsed (fmap B.blockQuote) +      "html"    -> withRaw'   (B.rawBlock blkType) +      "latex"   -> withRaw'   (B.rawBlock blkType) +      "ascii"   -> withRaw'   (B.rawBlock blkType) +      "example" -> withRaw'   exampleCode +      "quote"   -> withParsed B.blockQuote        "verse"   -> verseBlock        "src"     -> codeBlock -      _         -> withParsed (fmap $ divWithClass blkType) +      _         -> withParsed (divWithClass blkType)  blockHeaderStart :: OrgParser (Int, String)  blockHeaderStart = try $ (,) <$> indent <*> blockType @@ -365,10 +351,10 @@ blockHeaderStart = try $ (,) <$> indent <*> blockType    indent    = length      <$> many spaceChar    blockType = map toLower <$> (stringAnyCase "#+begin_" *> orgArgWord) -withRaw'   :: (String   -> F Blocks) -> BlockProperties -> OrgParser (F Blocks) +withRaw'   :: (String   -> Blocks) -> BlockProperties -> OrgParser Blocks  withRaw'   f blockProp = (ignHeaders *> (f <$> rawBlockContent blockProp)) -withParsed :: (F Blocks -> F Blocks) -> BlockProperties -> OrgParser (F Blocks) +withParsed :: (Blocks -> Blocks) -> BlockProperties -> OrgParser Blocks  withParsed f blockProp = (ignHeaders *> (f <$> parsedBlockContent blockProp))  ignHeaders :: OrgParser () @@ -377,11 +363,11 @@ ignHeaders = (() <$ newline) <|> (() <$ anyLine)  divWithClass :: String -> Blocks -> Blocks  divWithClass cls = B.divWith ("", [cls], []) -verseBlock :: BlockProperties -> OrgParser (F Blocks) +verseBlock :: BlockProperties -> OrgParser Blocks  verseBlock blkProp = try $ do    ignHeaders    content <- rawBlockContent blkProp -  fmap B.para . mconcat . intersperse (pure B.linebreak) +  B.para . mconcat . intersperse B.linebreak      <$> mapM (parseFromString parseInlines) (lines content)  exportsCode :: [(String, String)] -> Bool @@ -398,7 +384,7 @@ followingResultsBlock =                                       *> blankline                                       *> (unlines <$> many1 exampleLine)) -codeBlock :: BlockProperties -> OrgParser (F Blocks) +codeBlock :: BlockProperties -> OrgParser Blocks  codeBlock blkProp = do    skipSpaces    (classes, kv)     <- codeHeaderArgs <|> (mempty <$ ignHeaders) @@ -408,17 +394,15 @@ codeBlock blkProp = do    let includeCode    = exportsCode kv    let includeResults = exportsResults kv    let codeBlck       = B.codeBlockWith ( id', classes, kv ) content -  labelledBlck      <- maybe (pure codeBlck) -                             (labelDiv codeBlck) +  labelledBlck     <- maybe codeBlck (labelDiv codeBlck)                               <$> lookupInlinesAttr "caption" -  let resultBlck     = pure $ maybe mempty (exampleCode) resultsContent +  let resultBlck     = maybe mempty exampleCode resultsContent    return $ (if includeCode then labelledBlck else mempty)             <> (if includeResults then resultBlck else mempty)   where     labelDiv blk value = -       B.divWith nullAttr <$> (mappend <$> labelledBlock value -                                       <*> pure blk) -   labelledBlock = fmap (B.plain . B.spanWith ("", ["label"], [])) +       B.divWith nullAttr (labelledBlock value <> blk) +   labelledBlock =  B.plain . B.spanWith ("", ["label"], [])  rawBlockContent :: BlockProperties -> OrgParser String  rawBlockContent (indent, blockType) = try $ @@ -427,7 +411,7 @@ rawBlockContent (indent, blockType) = try $     indentedLine = try $ ("" <$ blankline) <|> (indentWith indent *> anyLine)     blockEnder = try $ indentWith indent *> stringAnyCase ("#+end_" <> blockType) -parsedBlockContent :: BlockProperties -> OrgParser (F Blocks) +parsedBlockContent :: BlockProperties -> OrgParser Blocks  parsedBlockContent blkProps = try $ do    raw <- rawBlockContent blkProps    parseFromString parseBlocks (raw ++ "\n") @@ -518,9 +502,9 @@ commaEscaped (',':cs@('*':_))     = cs  commaEscaped (',':cs@('#':'+':_)) = cs  commaEscaped cs                   = cs -example :: OrgParser (F Blocks) +example :: OrgParser Blocks  example = try $ do -  return . return . exampleCode =<< unlines <$> many1 exampleLine +  return . exampleCode =<< unlines <$> many1 exampleLine  exampleCode :: String -> Blocks  exampleCode = B.codeBlockWith ("", ["example"], []) @@ -529,7 +513,7 @@ exampleLine :: OrgParser String  exampleLine = try $ skipSpaces *> string ": " *> anyLine  -- Drawers for properties or a logbook -drawer :: OrgParser (F Blocks) +drawer :: OrgParser Blocks  drawer = try $ do    drawerStart    manyTill drawerLine (try drawerEnd) @@ -555,14 +539,12 @@ drawerEnd = try $  --  -- Figures (Image on a line by itself, preceded by name and/or caption) -figure :: OrgParser (F Blocks) +figure :: OrgParser Blocks  figure = try $ do    (cap, nam) <- nameAndCaption    src <- skipSpaces *> selfTarget <* skipSpaces <* P.newline    guard (isImageFilename src) -  return $ do -    cap' <- cap -    return $ B.para $ B.image src nam cap' +  return $ B.para $ B.image src nam cap   where     nameAndCaption =         do @@ -578,8 +560,8 @@ figure = try $ do  --  -- Comments, Options and Metadata -specialLine :: OrgParser (F Blocks) -specialLine = fmap return . try $ metaLine <|> commentLine +specialLine :: OrgParser Blocks +specialLine =  try $ metaLine <|> commentLine  metaLine :: OrgParser Blocks  metaLine = try $ mempty @@ -599,14 +581,14 @@ commentLineStart = try $ mappend <$> many spaceChar <*> string "# "  declarationLine :: OrgParser ()  declarationLine = try $ do    key <- metaKey -  inlinesF <- metaInlines +  inlines <- metaInlines    updateState $ \st -> -    let meta' = B.setMeta <$> pure key <*> inlinesF <*> pure nullMeta -    in st { orgStateMeta' = orgStateMeta' st <> meta' } +    let meta' = B.setMeta key inlines nullMeta +    in st { orgStateMeta = orgStateMeta st <> meta' }    return () -metaInlines :: OrgParser (F MetaValue) -metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline +metaInlines :: OrgParser MetaValue +metaInlines =  (MetaInlines . B.toList) <$> inlinesTillNewline  metaKey :: OrgParser String  metaKey = map toLower <$> many1 (noneOf ": \n\r") @@ -647,11 +629,11 @@ parseFormat = try $ do  --  -- | Headers -header :: OrgParser (F Blocks) +header :: OrgParser Blocks  header = try $ do    level <- headerStart    title <- inlinesTillNewline -  return $ B.header level <$> title +  return $ B.header level title  headerStart :: OrgParser Int  headerStart = try $ @@ -675,7 +657,7 @@ hline = try $ do  -- Tables  -- -data OrgTableRow = OrgContentRow (F [Blocks]) +data OrgTableRow = OrgContentRow [Blocks]                   | OrgAlignRow [Alignment]                   | OrgHlineRow @@ -686,13 +668,13 @@ data OrgTable = OrgTable    , orgTableRows       :: [[Blocks]]    } -table :: OrgParser (F Blocks) +table :: OrgParser Blocks  table = try $ do    lookAhead tableStart    do      rows <- tableRows -    cptn <- fromMaybe (pure "") <$> lookupInlinesAttr "caption" -    return $ (<$> cptn) . orgToPandocTable . normalizeTable =<< rowsToTable rows +    (cptn :: Inlines) <- fromMaybe "" <$> lookupInlinesAttr "caption" +    return $ ($ cptn) . orgToPandocTable . normalizeTable . rowsToTable $ rows  orgToPandocTable :: OrgTable                   -> Inlines @@ -708,11 +690,11 @@ tableRows = try $ many (tableAlignRow <|> tableHline <|> tableContentRow)  tableContentRow :: OrgParser OrgTableRow  tableContentRow = try $ -  OrgContentRow . sequence <$> (tableStart *> manyTill tableContentCell newline) +  OrgContentRow  <$> (tableStart *> manyTill tableContentCell newline) -tableContentCell :: OrgParser (F Blocks) +tableContentCell :: OrgParser Blocks  tableContentCell = try $ -  fmap B.plain . trimInlinesF . mconcat <$> many1Till inline endOfCell +  B.plain . trimInlines . mconcat <$> many1Till inline endOfCell  endOfCell :: OrgParser Char  endOfCell = try $ char '|' <|> lookAhead newline @@ -744,8 +726,8 @@ tableHline = try $    OrgHlineRow <$ (tableStart *> char '-' *> anyLine)  rowsToTable :: [OrgTableRow] -            -> F OrgTable -rowsToTable = foldM (flip rowToContent) zeroTable +            -> OrgTable +rowsToTable = foldl' (flip rowToContent) zeroTable    where zeroTable = OrgTable 0 mempty mempty mempty  normalizeTable :: OrgTable @@ -764,45 +746,43 @@ normalizeTable (OrgTable cols aligns heads lns) =  -- line as a header.  All other horizontal lines are discarded.  rowToContent :: OrgTableRow               -> OrgTable -             -> F OrgTable +             -> OrgTable  rowToContent OrgHlineRow        t = maybeBodyToHeader t -rowToContent (OrgAlignRow as)   t = setLongestRow as =<< setAligns as t -rowToContent (OrgContentRow rf) t = do -  rs <- rf -  setLongestRow rs =<< appendToBody rs t +rowToContent (OrgAlignRow as)   t = setLongestRow as . setAligns as $ t +rowToContent (OrgContentRow rf) t = setLongestRow rf .  appendToBody rf $ t  setLongestRow :: [a]                -> OrgTable -              -> F OrgTable +              -> OrgTable  setLongestRow rs t = -  return t{ orgTableColumns = max (length rs) (orgTableColumns t) } +  t{ orgTableColumns = max (length rs) (orgTableColumns t) }  maybeBodyToHeader :: OrgTable -                  -> F OrgTable +                  -> OrgTable  maybeBodyToHeader t = case t of    OrgTable{ orgTableHeader = [], orgTableRows = b:[] } -> -         return t{ orgTableHeader = b , orgTableRows = [] } -  _   -> return t +         t{ orgTableHeader = b , orgTableRows = [] } +  _   -> t  appendToBody :: [Blocks]               -> OrgTable -             -> F OrgTable -appendToBody r t = return t{ orgTableRows = orgTableRows t ++ [r] } +             -> OrgTable +appendToBody r t = t{ orgTableRows = orgTableRows t ++ [r] }  setAligns :: [Alignment]            -> OrgTable -          -> F OrgTable -setAligns aligns t = return $ t{ orgTableAlignments = aligns } +          -> OrgTable +setAligns aligns t = t{ orgTableAlignments = aligns }  --  -- LaTeX fragments  -- -latexFragment :: OrgParser (F Blocks) +latexFragment :: OrgParser Blocks  latexFragment = try $ do    envName <- latexEnvStart    content <- mconcat <$> manyTill anyLineNewline (latexEnd envName) -  return . return $ B.rawBlock "latex" (content `inLatexEnv` envName) +  return $ B.rawBlock "latex" (content `inLatexEnv` envName)   where     c `inLatexEnv` e = mconcat [ "\\begin{", e, "}\n"                                , c @@ -832,7 +812,7 @@ latexEnvName = try $ do  --  -- Footnote defintions  -- -noteBlock :: OrgParser (F Blocks) +noteBlock :: OrgParser Blocks  noteBlock = try $ do    ref <- noteMarker <* skipSpaces    content <- mconcat <$> blocksTillHeaderOrNote @@ -844,37 +824,37 @@ noteBlock = try $ do                            <|> () <$ lookAhead headerStart)  -- Paragraphs or Plain text -paraOrPlain :: OrgParser (F Blocks) +paraOrPlain :: OrgParser Blocks  paraOrPlain = try $ do    ils <- parseInlines    nl <- option False (newline >> return True)    try (guard nl >> notFollowedBy (orderedListStart <|> bulletListStart) >> -           return (B.para <$> ils)) -    <|>  (return (B.plain <$> ils)) +         (return $ B.para ils)) +    <|>  (return $ B.plain ils) -inlinesTillNewline :: OrgParser (F Inlines) -inlinesTillNewline = trimInlinesF . mconcat <$> manyTill inline newline +inlinesTillNewline :: OrgParser Inlines +inlinesTillNewline = trimInlines . mconcat <$> manyTill inline newline  --  -- list blocks  -- -list :: OrgParser (F Blocks) +list :: OrgParser Blocks  list = choice [ definitionList, bulletList, orderedList ] <?> "list" -definitionList :: OrgParser (F Blocks) +definitionList :: OrgParser Blocks  definitionList = try $ do n <- lookAhead (bulletListStart' Nothing) -                          fmap B.definitionList . fmap compactify'DL . sequence +                          B.definitionList . compactify'DL                              <$> many1 (definitionListItem $ bulletListStart' (Just n)) -bulletList :: OrgParser (F Blocks) +bulletList :: OrgParser Blocks  bulletList = try $ do n <- lookAhead (bulletListStart' Nothing) -                      fmap B.bulletList . fmap compactify' . sequence +                      B.bulletList . compactify'                          <$> many1 (listItem (bulletListStart' $ Just n)) -orderedList :: OrgParser (F Blocks) -orderedList = fmap B.orderedList . fmap compactify' . sequence +orderedList :: OrgParser Blocks +orderedList =  B.orderedList . compactify'                <$> many1 (listItem orderedListStart)  genericListStart :: OrgParser String @@ -911,7 +891,7 @@ orderedListStart = genericListStart orderedListMarker    where orderedListMarker = mappend <$> many1 digit <*> (pure <$> oneOf ".)")  definitionListItem :: OrgParser Int -                   -> OrgParser (F (Inlines, [Blocks])) +                   -> OrgParser (Inlines, [Blocks])  definitionListItem parseMarkerGetLength = try $ do    markerLength <- parseMarkerGetLength    term <- manyTill (noneOf "\n\r") (try $ string "::") @@ -920,12 +900,12 @@ definitionListItem parseMarkerGetLength = try $ do    cont <- concat <$> many (listContinuation markerLength)    term' <- parseFromString parseInlines term    contents' <- parseFromString parseBlocks $ line1 ++ blank ++ cont -  return $ (,) <$> term' <*> fmap (:[]) contents' +  return (term', [contents'])  -- parse raw text for one list item, excluding start marker and continuations  listItem :: OrgParser Int -         -> OrgParser (F Blocks) +         -> OrgParser Blocks  listItem start = try $ do    markerLength <- try start    firstLine <- anyLineNewline @@ -951,7 +931,7 @@ anyLineNewline = (++ "\n") <$> anyLine  -- inline  -- -inline :: OrgParser (F Inlines) +inline :: OrgParser Inlines  inline =    choice [ whitespace           , linebreak @@ -978,31 +958,31 @@ inline =           ] <* (guard =<< newlinesCountWithinLimits)    <?> "inline" -parseInlines :: OrgParser (F Inlines) -parseInlines = trimInlinesF . mconcat <$> many1 inline +parseInlines :: OrgParser Inlines +parseInlines = trimInlines . mconcat <$> many1 inline  -- treat these as potentially non-text when parsing inline:  specialChars :: [Char]  specialChars = "\"$'()*+-,./:<=>[\\]^_{|}~" -whitespace :: OrgParser (F Inlines) -whitespace = pure B.space <$ skipMany1 spaceChar +whitespace :: OrgParser Inlines +whitespace = B.space <$ skipMany1 spaceChar                            <* updateLastPreCharPos                            <* updateLastForbiddenCharPos               <?> "whitespace" -linebreak :: OrgParser (F Inlines) -linebreak = try $ pure B.linebreak <$ string "\\\\" <* skipSpaces <* newline +linebreak :: OrgParser Inlines +linebreak = try $ B.linebreak <$ string "\\\\" <* skipSpaces <* newline -str :: OrgParser (F Inlines) -str = return . B.str <$> many1 (noneOf $ specialChars ++ "\n\r ") +str :: OrgParser Inlines +str = B.str <$> many1 (noneOf $ specialChars ++ "\n\r ")        <* updateLastStrPos  -- | An endline character that can be treated as a space, not a structural  -- break.  This should reflect the values of the Emacs variable  -- @org-element-pagaraph-separate@. -endline :: OrgParser (F Inlines) +endline :: OrgParser Inlines  endline = try $ do    newline    notFollowedBy blankline @@ -1020,77 +1000,72 @@ endline = try $ do    decEmphasisNewlinesCount    guard =<< newlinesCountWithinLimits    updateLastPreCharPos -  return . return $ B.space +  return $ B.space -cite :: OrgParser (F Inlines) +cite :: OrgParser Inlines  cite = try $ do    guardEnabled Ext_citations    (cs, raw) <- withRaw normalCite -  return $ (flip B.cite (B.text raw)) <$> cs +  return $ flip B.cite (B.text raw) cs -normalCite :: OrgParser (F [Citation]) +normalCite :: OrgParser [Citation]  normalCite = try $  char '['                   *> skipSpaces                   *> citeList                   <* skipSpaces                   <* char ']' -citeList :: OrgParser (F [Citation]) -citeList = sequence <$> sepBy1 citation (try $ char ';' *> skipSpaces) +citeList :: OrgParser [Citation] +citeList = sepBy1 citation (try $ char ';' *> skipSpaces) -citation :: OrgParser (F Citation) +citation :: OrgParser Citation  citation = try $ do    pref <- prefix    (suppress_author, key) <- citeKey    suff <- suffix -  return $ do -    x <- pref -    y <- suff -    return $ Citation{ citationId      = key -                     , citationPrefix  = B.toList x -                     , citationSuffix  = B.toList y -                     , citationMode    = if suppress_author -                                            then SuppressAuthor -                                            else NormalCitation -                     , citationNoteNum = 0 -                     , citationHash    = 0 -                     } +  return $ Citation{ citationId      = key +                   , citationPrefix  = B.toList pref +                   , citationSuffix  = B.toList suff +                   , citationMode    = if suppress_author +                                          then SuppressAuthor +                                          else NormalCitation +                   , citationNoteNum = 0 +                   , citationHash    = 0 +                   }   where -   prefix = trimInlinesF . mconcat <$> +   prefix = trimInlines . mconcat <$>              manyTill inline (char ']' <|> (']' <$ lookAhead citeKey))     suffix = try $ do       hasSpace <- option False (notFollowedBy nonspaceChar >> return True)       skipSpaces -     rest <- trimInlinesF . mconcat <$> +     rest <- trimInlines . mconcat <$>               many (notFollowedBy (oneOf ";]") *> inline) -     return $ if hasSpace -              then (B.space <>) <$> rest -              else rest +     return $ +      if hasSpace +        then B.space <> rest +        else rest -footnote :: OrgParser (F Inlines) +footnote :: OrgParser Inlines  footnote = try $ inlineNote <|> referencedNote -inlineNote :: OrgParser (F Inlines) +inlineNote :: OrgParser Inlines  inlineNote = try $ do    string "[fn:"    ref <- many alphaNum    char ':' -  note <- fmap B.para . trimInlinesF . mconcat <$> many1Till inline (char ']') +  note <- B.para . trimInlines . mconcat <$> many1Till inline (char ']')    when (not $ null ref) $         addToNotesTable ("fn:" ++ ref, note) -  return $ B.note <$> note +  return $ B.note note -referencedNote :: OrgParser (F Inlines) +referencedNote :: OrgParser Inlines  referencedNote = try $ do    ref <- noteMarker -  return $ do -    notes <- asksF orgStateNotes' +  notes <- asks (orgStateNotes' . finalState) +  return $      case lookup ref notes of -      Nothing   -> return $ B.str $ "[" ++ ref ++ "]" -      Just contents  -> do -        st <- askF -        let contents' = runF contents st{ orgStateNotes' = [] } -        return $ B.note contents' +      Just contents  -> B.note contents +      Nothing   -> B.str $ "[" ++ ref ++ "]"  noteMarker :: OrgParser String  noteMarker = try $ do @@ -1100,37 +1075,37 @@ noteMarker = try $ do                  <*> many1Till (noneOf "\n\r\t ") (char ']')           ] -linkOrImage :: OrgParser (F Inlines) +linkOrImage :: OrgParser Inlines  linkOrImage = explicitOrImageLink                <|> selflinkOrImage                <|> angleLink                <|> plainLink                <?> "link or image" -explicitOrImageLink :: OrgParser (F Inlines) +explicitOrImageLink :: OrgParser Inlines  explicitOrImageLink = try $ do    char '[' -  srcF   <- applyCustomLinkFormat =<< possiblyEmptyLinkTarget +  src   <- applyCustomLinkFormat =<< possiblyEmptyLinkTarget    title  <- enclosedRaw (char '[') (char ']')    title' <- parseFromString (mconcat <$> many inline) title    char ']' -  return $ do -    src <- srcF -    if isImageFilename src && isImageFilename title -      then pure $ B.link src "" $ B.image title mempty mempty -      else linkToInlinesF src =<< title' +  alt <- internalLink src title' +  return $ +    (if isImageFilename src && isImageFilename title +      then B.link src "" $ B.image title mempty mempty +      else fromMaybe alt (linkToInlines src title')) -selflinkOrImage :: OrgParser (F Inlines) +selflinkOrImage :: OrgParser Inlines  selflinkOrImage = try $ do    src <- char '[' *> linkTarget <* char ']' -  return $ linkToInlinesF src (B.str src) +  return $ fromMaybe "" (linkToInlines src (B.str src)) -plainLink :: OrgParser (F Inlines) +plainLink :: OrgParser Inlines  plainLink = try $ do    (orig, src) <- uri -  returnF $ B.link src "" (B.str orig) +  return $ B.link src "" (B.str orig) -angleLink :: OrgParser (F Inlines) +angleLink :: OrgParser Inlines  angleLink = try $ do    char '<'    link <- plainLink @@ -1146,26 +1121,31 @@ linkTarget = enclosedByPair '[' ']' (noneOf "\n\r[]")  possiblyEmptyLinkTarget :: OrgParser String  possiblyEmptyLinkTarget = try linkTarget <|> ("" <$ string "[]") -applyCustomLinkFormat :: String -> OrgParser (F String) +applyCustomLinkFormat :: String -> OrgParser String  applyCustomLinkFormat link = do    let (linkType, rest) = break (== ':') link -  return $ do -    formatter <- M.lookup linkType <$> asksF orgStateLinkFormatters -    return $ maybe link ($ drop 1 rest) formatter +  fmts <- asks finalState +  return $ +    case M.lookup linkType (orgStateLinkFormatters fmts) of +         Just v    -> (v (drop 1 rest)) +         Nothing   -> link  -- TODO: might be a lot smarter/cleaner to use parsec and ADTs for this kind  -- of parsing. -linkToInlinesF :: String -> Inlines -> F Inlines -linkToInlinesF s = +linkToInlines :: String -> Inlines -> Maybe Inlines +linkToInlines = \s ->    case s of -    ""      -> pure . B.link "" "" -    ('#':_) -> pure . B.link s "" -    _ | isImageFilename s     -> const . pure $ B.image s "" "" -    _ | isFileLink s          -> pure . B.link (dropLinkType s) "" -    _ | isUri s               -> pure . B.link s "" -    _ | isAbsoluteFilePath s  -> pure . B.link ("file://" ++ s) "" -    _ | isRelativeFilePath s  -> pure . B.link s "" -    _                         -> internalLink s +    _ | null s    -> Just . B.link "" "" +    _ | isAnchor s  -> Just . B.link s "" +    _ | isImageFilename s     -> const . Just $ B.image s "" "" +    _ | isFileLink s          -> Just . B.link (dropLinkType s) "" +    _ | isUri s               -> Just . B.link s "" +    _ | isAbsoluteFilePath s  -> Just . B.link ("file://" ++ s) "" +    _ | isRelativeFilePath s  -> Just . B.link s "" +    _                         -> const Nothing + +isAnchor :: String -> Bool +isAnchor s = "#" `isPrefixOf` s  isFileLink :: String -> Bool  isFileLink s = ("file:" `isPrefixOf` s) && not ("file://" `isPrefixOf` s) @@ -1194,12 +1174,13 @@ isImageFilename filename =     imageExtensions = [ "jpeg" , "jpg" , "png" , "gif" , "svg" ]     protocols = [ "file", "http", "https" ] -internalLink :: String -> Inlines -> F Inlines +internalLink :: String -> Inlines -> OrgParser Inlines  internalLink link title = do -  anchorB <- (link `elem`) <$> asksF orgStateAnchorIds -  if anchorB -    then return $ B.link ('#':link) "" title -    else return $ B.emph title +  anchorB <- asks finalState +  return  $ +    if link `elem` (orgStateAnchorIds anchorB) +      then B.link ('#':link) "" title +      else B.emph title  -- | Parse an anchor like @<<anchor-id>>@ and return an empty span with  -- @anchor-id@ set as id.  Legal anchors in org-mode are defined through @@ -1207,11 +1188,11 @@ internalLink link title = do  -- @anchor-id@ contains spaces, we are more restrictive in what is accepted as  -- an anchor. -anchor :: OrgParser (F Inlines) +anchor :: OrgParser Inlines  anchor =  try $ do    anchorId <- parseAnchor    recordAnchorId anchorId -  returnF $ B.spanWith (solidify anchorId, [], []) mempty +  return $ B.spanWith (solidify anchorId, [], []) mempty   where         parseAnchor = string "<<"                       *> many1 (noneOf "\t\n\r<>\"' ") @@ -1229,7 +1210,7 @@ solidify = map replaceSpecialChar             | otherwise       = '-'  -- | Parses an inline code block and marks it as an babel block. -inlineCodeBlock :: OrgParser (F Inlines) +inlineCodeBlock :: OrgParser Inlines  inlineCodeBlock = try $ do    string "src_"    lang <- many1 orgArgWordChar @@ -1237,7 +1218,7 @@ inlineCodeBlock = try $ do    inlineCode <- enclosedByPair '{' '}' (noneOf "\n\r")    let attrClasses = [translateLang lang, rundocBlockClass]    let attrKeyVal  = map toRundocAttrib (("language", lang) : opts) -  returnF $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode +  return $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode  enclosedByPair :: Char          -- ^ opening char                 -> Char          -- ^ closing char @@ -1245,41 +1226,40 @@ enclosedByPair :: Char          -- ^ opening char                 -> OrgParser [a]  enclosedByPair s e p = char s *> many1Till p (char e) -emph      :: OrgParser (F Inlines) -emph      = fmap B.emph         <$> emphasisBetween '/' +emph      :: OrgParser Inlines +emph      =  B.emph         <$> emphasisBetween '/' -strong    :: OrgParser (F Inlines) -strong    = fmap B.strong       <$> emphasisBetween '*' +strong    :: OrgParser Inlines +strong    =  B.strong       <$> emphasisBetween '*' -strikeout :: OrgParser (F Inlines) -strikeout = fmap B.strikeout    <$> emphasisBetween '+' +strikeout :: OrgParser Inlines +strikeout =  B.strikeout    <$> emphasisBetween '+'  -- There is no underline, so we use strong instead. -underline :: OrgParser (F Inlines) -underline = fmap B.strong       <$> emphasisBetween '_' +underline :: OrgParser Inlines +underline =  B.strong       <$> emphasisBetween '_' -verbatim  :: OrgParser (F Inlines) -verbatim  = return . B.code     <$> verbatimBetween '=' +verbatim  :: OrgParser Inlines +verbatim  = B.code     <$> verbatimBetween '=' -code      :: OrgParser (F Inlines) -code      = return . B.code     <$> verbatimBetween '~' +code      :: OrgParser Inlines +code      = B.code     <$> verbatimBetween '~' -subscript   :: OrgParser (F Inlines) -subscript   = fmap B.subscript   <$> try (char '_' *> subOrSuperExpr) +subscript   :: OrgParser Inlines +subscript   =  B.subscript   <$> try (char '_' *> subOrSuperExpr) -superscript :: OrgParser (F Inlines) -superscript = fmap B.superscript <$> try (char '^' *> subOrSuperExpr) +superscript :: OrgParser Inlines +superscript =  B.superscript <$> try (char '^' *> subOrSuperExpr) -math      :: OrgParser (F Inlines) -math      = return . B.math      <$> choice [ math1CharBetween '$' +math      :: OrgParser Inlines +math      = B.math      <$> choice [ math1CharBetween '$'                                              , mathStringBetween '$'                                              , rawMathBetween "\\(" "\\)"                                              ] -displayMath :: OrgParser (F Inlines) -displayMath = return . B.displayMath <$> choice [ rawMathBetween "\\[" "\\]" -                                                , rawMathBetween "$$"  "$$" -                                                ] +displayMath :: OrgParser Inlines +displayMath = B.displayMath <$> choice [ rawMathBetween "\\[" "\\]" +                                       , rawMathBetween "$$"  "$$" ]  updatePositions :: Char                  -> OrgParser (Char) @@ -1288,11 +1268,11 @@ updatePositions c = do    when (c `elem` emphasisForbiddenBorderChars) updateLastForbiddenCharPos    return c -symbol :: OrgParser (F Inlines) -symbol = return . B.str . (: "") <$> (oneOf specialChars >>= updatePositions) +symbol :: OrgParser Inlines +symbol = B.str . (: "") <$> (oneOf specialChars >>= updatePositions)  emphasisBetween :: Char -                -> OrgParser (F Inlines) +                -> OrgParser Inlines  emphasisBetween c = try $ do    startEmphasisNewlinesCounting emphasisAllowedNewlines    res <- enclosedInlines (emphasisStart c) (emphasisEnd c) @@ -1369,9 +1349,9 @@ mathEnd c = try $ do  enclosedInlines :: OrgParser a                  -> OrgParser b -                -> OrgParser (F Inlines) +                -> OrgParser Inlines  enclosedInlines start end = try $ -  trimInlinesF . mconcat <$> enclosed start end inline +  trimInlines . mconcat <$> enclosed start end inline  enclosedRaw :: OrgParser a              -> OrgParser b @@ -1450,7 +1430,7 @@ notAfterForbiddenBorderChar = do    return $ lastFBCPos /= Just pos  -- | Read a sub- or superscript expression -subOrSuperExpr :: OrgParser (F Inlines) +subOrSuperExpr :: OrgParser Inlines  subOrSuperExpr = try $    choice [ id                   <$> charsInBalanced '{' '}' (noneOf "\n\r")           , enclosing ('(', ')') <$> charsInBalanced '(' ')' (noneOf "\n\r") @@ -1465,10 +1445,10 @@ simpleSubOrSuperString = try $                     <*> many1 alphaNum           ] -inlineLaTeX :: OrgParser (F Inlines) +inlineLaTeX :: OrgParser Inlines  inlineLaTeX = try $ do    cmd <- inlineLaTeXCommand -  maybe mzero returnF $ +  maybe mzero return $       parseAsMath cmd `mplus` parseAsMathMLSym cmd `mplus` parseAsInlineLaTeX cmd   where     parseAsMath :: String -> Maybe Inlines @@ -1501,30 +1481,30 @@ inlineLaTeXCommand = try $ do        return cs      _ -> mzero -smart :: OrgParser (F Inlines) +smart :: OrgParser Inlines  smart = do    getOption readerSmart >>= guard    doubleQuoted <|> singleQuoted <|> -    choice (map (return <$>) [orgApostrophe, dash, ellipses]) +    choice [orgApostrophe, dash, ellipses]    where orgApostrophe =            (char '\'' <|> char '\8217') <* updateLastPreCharPos                                         <* updateLastForbiddenCharPos                                         *> return (B.str "\x2019") -singleQuoted :: OrgParser (F Inlines) +singleQuoted :: OrgParser Inlines  singleQuoted = try $ do    singleQuoteStart    withQuoteContext InSingleQuote $ -    fmap B.singleQuoted . trimInlinesF . mconcat <$> +    B.singleQuoted . trimInlines . mconcat <$>        many1Till inline singleQuoteEnd  -- doubleQuoted will handle regular double-quoted sections, as well  -- as dialogues with an open double-quote without a close double-quote  -- in the same paragraph. -doubleQuoted :: OrgParser (F Inlines) +doubleQuoted :: OrgParser Inlines  doubleQuoted = try $ do    doubleQuoteStart    contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline)    (withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return -       (fmap B.doubleQuoted . trimInlinesF $ contents)) -   <|> (return $ return (B.str "\8220") <> contents) +       (B.doubleQuoted . trimInlines $ contents)) +   <|> (return $ (B.str "\8220") <> contents) diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index b9a77c5d6..4ae9d52ae 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -58,7 +58,7 @@ readRST :: ReaderOptions -- ^ Reader options  readRST opts s = (readWith parseRST) def{ stateOptions = opts } (s ++ "\n\n")  readRSTWithWarnings :: ReaderOptions -> String -> (Pandoc, [String]) -readRSTWithWarnings opts s = (readWithWarnings parseRST) def{ stateOptions = opts } (s ++ "\n\n") +readRSTWithWarnings opts s = (readWith (returnWarnings parseRST)) def{ stateOptions = opts } (s ++ "\n\n")  type RSTParser = Parser [Char] ParserState | 
