diff options
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/BlockStarts.hs | 9 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 63 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/DocumentTree.hs | 25 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 64 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Meta.hs | 9 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 1 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 2 | 
7 files changed, 84 insertions, 89 deletions
| diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index fb2b52654..9c6614c99 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -66,7 +66,7 @@ gridTableStart = try $ skipSpaces <* char '+' <* char '-'  latexEnvStart :: Monad m => OrgParser m String -latexEnvStart = try $ do +latexEnvStart = try $    skipSpaces *> string "\\begin{"               *> latexEnvName               <* string "}" @@ -97,8 +97,7 @@ orderedListStart = genericListStart orderedListMarker    where orderedListMarker = mappend <$> many1 digit <*> (pure <$> oneOf ".)")  drawerStart :: Monad m => OrgParser m String -drawerStart = try $ -  skipSpaces *> drawerName <* skipSpaces <* newline +drawerStart = try $ skipSpaces *> drawerName <* skipSpaces <* newline   where drawerName = char ':' *> manyTill nonspaceChar (char ':')  metaLineStart :: Monad m => OrgParser m () @@ -120,8 +119,8 @@ noteMarker = try $ do  -- | Succeeds if the parser is at the end of a block.  endOfBlock :: Monad m => OrgParser m () -endOfBlock = lookAhead . try $ do -    void blankline <|> anyBlockStart +endOfBlock = lookAhead . try $ +  void blankline <|> anyBlockStart   where     -- Succeeds if there is a new block starting at this position.     anyBlockStart :: Monad m => OrgParser m () diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index b650721b3..f669abc27 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -17,7 +17,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  -}  {-# LANGUAGE FlexibleContexts #-}  {-# LANGUAGE RecordWildCards  #-} -{-# LANGUAGE ViewPatterns     #-}  {- |     Module      : Text.Pandoc.Readers.Org.Blocks     Copyright   : Copyright (C) 2014-2017 Albert Krewinkel @@ -52,7 +51,7 @@ import Control.Monad (foldM, guard, mzero, void)  import Data.Char (isSpace, toLower, toUpper)  import Data.Default (Default)  import Data.List (foldl', isPrefixOf) -import Data.Maybe (fromMaybe, isNothing) +import Data.Maybe (fromMaybe, isJust, isNothing)  import Data.Monoid ((<>))  -- @@ -113,7 +112,7 @@ data BlockAttributes = BlockAttributes  -- | Convert BlockAttributes into pandoc Attr  attrFromBlockAttributes :: BlockAttributes -> Attr -attrFromBlockAttributes (BlockAttributes{..}) = +attrFromBlockAttributes BlockAttributes{..} =    let      ident   = fromMaybe mempty $ lookup "id" blockAttrKeyValues      classes = case lookup "class" blockAttrKeyValues of @@ -142,7 +141,7 @@ blockAttributes = try $ do                     Nothing -> return Nothing                     Just s  -> Just <$> parseFromString inlines (s ++ "\n")    kvAttrs' <- parseFromString keyValues . (++ "\n") $ fromMaybe mempty kvAttrs -  return $ BlockAttributes +  return BlockAttributes             { blockAttrName = name             , blockAttrLabel = label             , blockAttrCaption = caption' @@ -187,7 +186,7 @@ orgBlock = try $ do    blockAttrs <- blockAttributes    blkType <- blockHeaderStart    ($ blkType) $ -    case (map toLower blkType) of +    case map toLower blkType of        "export"  -> exportBlock        "comment" -> rawBlockLines (const mempty)        "html"    -> rawBlockLines (return . B.rawBlock (lowercase blkType)) @@ -208,10 +207,10 @@ orgBlock = try $ do     lowercase = map toLower  rawBlockLines :: Monad m => (String   -> F Blocks) -> String -> OrgParser m (F Blocks) -rawBlockLines f blockType = (ignHeaders *> (f <$> rawBlockContent blockType)) +rawBlockLines f blockType = ignHeaders *> (f <$> rawBlockContent blockType)  parseBlockLines :: PandocMonad m => (F Blocks -> F Blocks) -> String -> OrgParser m (F Blocks) -parseBlockLines f blockType = (ignHeaders *> (f <$> parsedBlockContent)) +parseBlockLines f blockType = ignHeaders *> (f <$> parsedBlockContent)   where     parsedBlockContent :: PandocMonad m => OrgParser m (F Blocks)     parsedBlockContent = try $ do @@ -239,8 +238,7 @@ rawBlockContent blockType = try $ do     stripIndent strs = map (drop (shortestIndent strs)) strs     shortestIndent :: [String] -> Int -   shortestIndent = foldr min maxBound -                    . map (length . takeWhile isSpace) +   shortestIndent = foldr (min . length . takeWhile isSpace) maxBound                      . filter (not . null)     tabsToSpaces :: Int -> String -> String @@ -336,13 +334,13 @@ codeHeaderArgs = try $ do    language   <- skipSpaces *> orgArgWord    (switchClasses, switchKv) <- switchesAsAttributes    parameters <- manyTill blockOption newline -  return $ ( translateLang language : switchClasses -           , originalLang language <> switchKv <> parameters -           ) +  return ( translateLang language : switchClasses +         , originalLang language <> switchKv <> parameters +         )  switchesAsAttributes :: Monad m => OrgParser m ([String], [(String, String)])  switchesAsAttributes = try $ do -  switches <- skipSpaces *> (try $ switch `sepBy` (many1 spaceChar)) +  switches <- skipSpaces *> try (switch `sepBy` many1 spaceChar)    return $ foldr addToAttr ([], []) switches   where    addToAttr :: (Char, Maybe String, SwitchPolarity) @@ -350,7 +348,7 @@ switchesAsAttributes = try $ do              -> ([String], [(String, String)])    addToAttr ('n', lineNum, pol) (cls, kv) =      let kv' = case lineNum of -                Just num -> (("startFrom", num):kv) +                Just num -> ("startFrom", num):kv                  Nothing  -> kv          cls' = case pol of                   SwitchPlus -> "continuedSourceBlock":cls @@ -382,7 +380,7 @@ genericSwitch :: Monad m  genericSwitch c p = try $ do    polarity <- switchPolarity <* char c <* skipSpaces    arg <- optionMaybe p -  return $ (c, arg, polarity) +  return (c, arg, polarity)  -- | Reads a line number switch option. The line number switch can be used with  -- example and source blocks. @@ -402,8 +400,8 @@ orgParamValue = try $      *> noneOf "\n\r" `many1Till` endOfValue      <* skipSpaces   where -  endOfValue = lookAhead $  (try $ skipSpaces <* oneOf "\n\r") -                        <|> (try $ skipSpaces1 <* orgArgKey) +  endOfValue = lookAhead $  try (skipSpaces <* oneOf "\n\r") +                        <|> try (skipSpaces1 <* orgArgKey)  -- @@ -421,7 +419,7 @@ genericDrawer = try $ do    -- Include drawer if it is explicitly included in or not explicitly excluded    -- from the list of drawers that should be exported.  PROPERTIES drawers are    -- never exported. -  case (exportDrawers . orgStateExportSettings $ state) of +  case exportDrawers . orgStateExportSettings $ state of      _           | name == "PROPERTIES" -> return mempty      Left  names | name `elem`    names -> return mempty      Right names | name `notElem` names -> return mempty @@ -455,7 +453,7 @@ figure = try $ do      Nothing     -> mzero      Just imgSrc -> do        guard (isImageFilename imgSrc) -      let isFigure = not . isNothing $ blockAttrCaption figAttrs +      let isFigure = isJust $ blockAttrCaption figAttrs        return $ imageBlock isFigure figAttrs imgSrc   where     selfTarget :: PandocMonad m => OrgParser m String @@ -490,8 +488,7 @@ endOfParagraph = try $ skipSpaces *> newline *> endOfBlock  -- | Example code marked up by a leading colon.  example :: Monad m => OrgParser m (F Blocks) -example = try $ do -  returnF . exampleCode =<< unlines <$> many1 exampleLine +example = try $ returnF . exampleCode =<< unlines <$> many1 exampleLine   where     exampleLine :: Monad m => OrgParser m String     exampleLine = try $ exampleLineStart *> anyLine @@ -514,7 +511,7 @@ include = try $ do    filename <- includeTarget    blockType <- optionMaybe $ skipSpaces *> many1 alphaNum    blocksParser <- case blockType of -                    Just "example" -> do +                    Just "example" ->                        return $ pure . B.codeBlock <$> parseRaw                      Just "export" -> do                        format <- skipSpaces *> many (noneOf "\n\r\t ") @@ -580,8 +577,8 @@ orgTable :: PandocMonad m => OrgParser m (F Blocks)  orgTable = try $ do    -- don't allow a table on the first line of a list item; org requires that    -- tables start at first non-space character on the line -  let isFirstInListItem st = (orgStateParserContext st == ListItemState) && -                             (orgStateLastPreCharPos st == Nothing) +  let isFirstInListItem st = orgStateParserContext st == ListItemState && +                             isNothing (orgStateLastPreCharPos st)    guard =<< not . isFirstInListItem <$> getState    blockAttrs <- blockAttributes    lookAhead tableStart @@ -594,7 +591,7 @@ orgToPandocTable :: OrgTable                   -> Inlines                   -> Blocks  orgToPandocTable (OrgTable colProps heads lns) caption = -  let totalWidth = if any (not . isNothing) (map columnRelWidth colProps) +  let totalWidth = if any isJust (map columnRelWidth colProps)                     then Just . sum $ map (fromMaybe 1 . columnRelWidth) colProps                     else Nothing    in B.table caption (map (convertColProp totalWidth) colProps) heads lns @@ -604,7 +601,7 @@ orgToPandocTable (OrgTable colProps heads lns) caption =       let         align' = fromMaybe AlignDefault $ columnAlignment colProp         width' = fromMaybe 0 $ (\w t -> (fromIntegral w / fromIntegral t)) -                              <$> (columnRelWidth colProp) +                              <$> columnRelWidth colProp                                <*> totalWidth       in (align', width') @@ -630,7 +627,7 @@ tableAlignRow = try $ do  columnPropertyCell :: Monad m => OrgParser m ColumnProperty  columnPropertyCell = emptyCell <|> propCell <?> "alignment info"   where -   emptyCell = ColumnProperty Nothing Nothing <$ (try $ skipSpaces *> endOfCell) +   emptyCell = ColumnProperty Nothing Nothing <$ try (skipSpaces *> endOfCell)     propCell = try $ ColumnProperty                   <$> (skipSpaces                        *> char '<' @@ -684,7 +681,7 @@ rowToContent tbl row =   where     singleRowPromotedToHeader :: OrgTable     singleRowPromotedToHeader = case tbl of -     OrgTable{ orgTableHeader = [], orgTableRows = b:[] } -> +     OrgTable{ orgTableHeader = [], orgTableRows = [b] } ->              tbl{ orgTableHeader = b , orgTableRows = [] }       _   -> tbl @@ -739,7 +736,7 @@ noteBlock = try $ do  paraOrPlain :: PandocMonad m => OrgParser m (F Blocks)  paraOrPlain = try $ do    -- Make sure we are not looking at a headline -  notFollowedBy' (char '*' *> (oneOf " *")) +  notFollowedBy' (char '*' *> oneOf " *")    ils <- inlines    nl <- option False (newline *> return True)    -- Read block as paragraph, except if we are in a list context and the block @@ -748,7 +745,7 @@ paraOrPlain = try $ do    try (guard nl         *> notFollowedBy (inList *> (() <$ orderedListStart <|> bulletListStart))         *> return (B.para <$> ils)) -    <|>  (return (B.plain <$> ils)) +    <|>  return (B.plain <$> ils)  -- @@ -760,16 +757,16 @@ list = choice [ definitionList, bulletList, orderedList ] <?> "list"  definitionList :: PandocMonad m => OrgParser m (F Blocks)  definitionList = try $ do n <- lookAhead (bulletListStart' Nothing) -                          fmap B.definitionList . fmap compactifyDL . sequence +                          fmap (B.definitionList . compactifyDL) . sequence                              <$> many1 (definitionListItem $ bulletListStart' (Just n))  bulletList :: PandocMonad m => OrgParser m (F Blocks)  bulletList = try $ do n <- lookAhead (bulletListStart' Nothing) -                      fmap B.bulletList . fmap compactify . sequence +                      fmap (B.bulletList . compactify) . sequence                          <$> many1 (listItem (bulletListStart' $ Just n))  orderedList :: PandocMonad m => OrgParser m (F Blocks) -orderedList = fmap B.orderedList . fmap compactify . sequence +orderedList = fmap (B.orderedList . compactify) . sequence                <$> many1 (listItem orderedListStart)  bulletListStart' :: Monad m => Maybe Int -> OrgParser m Int diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index 4abbe7be8..cee740e30 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -32,10 +32,10 @@ module Text.Pandoc.Readers.Org.DocumentTree    , headlineToBlocks    ) where +import Control.Arrow ((***))  import Control.Monad (guard, void)  import Data.Char (toLower, toUpper)  import Data.List ( intersperse ) -import Data.Maybe (fromMaybe)  import Data.Monoid ((<>))  import Text.Pandoc.Builder (Blocks, Inlines)  import Text.Pandoc.Class (PandocMonad) @@ -142,7 +142,7 @@ headline blocks inline lvl = try $ do      title'    <- title      contents' <- contents      children' <- sequence children -    return $ Headline +    return Headline        { headlineLevel = level        , headlineTodoMarker = todoKw        , headlineText = title' @@ -162,7 +162,7 @@ headline blocks inline lvl = try $ do  -- | Convert an Org mode headline (i.e. a document tree) into pandoc's Blocks  headlineToBlocks :: Monad m => Headline -> OrgParser m Blocks -headlineToBlocks hdln@(Headline {..}) = do +headlineToBlocks hdln@Headline {..} = do    maxHeadlineLevels <- getExportSetting exportHeadlineLevels    case () of      _ | any isNoExportTag headlineTags     -> return mempty @@ -193,7 +193,7 @@ archivedHeadlineToBlocks hdln = do      ArchivedTreesHeadlineOnly -> headlineToHeader hdln  headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks -headlineToHeaderWithList hdln@(Headline {..}) = do +headlineToHeaderWithList hdln@Headline {..} = do    maxHeadlineLevels <- getExportSetting exportHeadlineLevels    header        <- headlineToHeader hdln    listElements  <- mapM headlineToBlocks headlineChildren @@ -212,13 +212,13 @@ headlineToHeaderWithList hdln@(Headline {..}) = do         _                    -> mempty  headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks -headlineToHeaderWithContents hdln@(Headline {..}) = do +headlineToHeaderWithContents hdln@Headline {..} = do    header         <- headlineToHeader hdln    childrenBlocks <- mconcat <$> mapM headlineToBlocks headlineChildren    return $ header <> headlineContents <> childrenBlocks  headlineToHeader :: Monad m => Headline -> OrgParser m Blocks -headlineToHeader (Headline {..}) = do +headlineToHeader Headline {..} = do    exportTodoKeyword <- getExportSetting exportWithTodoKeywords    exportTags        <- getExportSetting exportWithTags    let todoText    = if exportTodoKeyword @@ -237,7 +237,7 @@ headlineToHeader (Headline {..}) = do  todoKeyword :: Monad m => OrgParser m TodoMarker  todoKeyword = try $ do    taskStates <- activeTodoMarkers <$> getState -  let kwParser tdm = try $ (tdm <$ string (todoMarkerName tdm) <* spaceChar) +  let kwParser tdm = try (tdm <$ string (todoMarkerName tdm) <* spaceChar)    choice (map kwParser taskStates)  todoKeywordToInlines :: TodoMarker -> Inlines @@ -250,19 +250,19 @@ todoKeywordToInlines tdm =  propertiesToAttr :: Properties -> Attr  propertiesToAttr properties =    let -    toStringPair prop = (fromKey (fst prop), fromValue (snd prop)) +    toStringPair = fromKey *** fromValue      customIdKey = toPropertyKey "custom_id"      classKey    = toPropertyKey "class"      unnumberedKey = toPropertyKey "unnumbered"      specialProperties = [customIdKey, classKey, unnumberedKey] -    id'  = fromMaybe mempty . fmap fromValue . lookup customIdKey $ properties -    cls  = fromMaybe mempty . fmap fromValue . lookup classKey    $ properties +    id'  = maybe mempty fromValue . lookup customIdKey $ properties +    cls  = maybe mempty fromValue . lookup classKey    $ properties      kvs' = map toStringPair . filter ((`notElem` specialProperties) . fst)             $ properties      isUnnumbered = -      fromMaybe False . fmap isNonNil . lookup unnumberedKey $ properties +      maybe False isNonNil . lookup unnumberedKey $ properties    in -    (id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs') +    (id', words cls ++ ["unnumbered" | isUnnumbered], kvs')  tagsToInlines :: [Tag] -> Inlines  tagsToInlines [] = mempty @@ -302,4 +302,3 @@ propertiesDrawer = try $ do     endOfDrawer :: Monad m => OrgParser m String     endOfDrawer = try $       skipSpaces *> stringAnyCase ":END:" <* skipSpaces <* newline - diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index ad5a1e4de..af28701d7 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -48,7 +48,7 @@ import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)  import Text.TeXMath (DisplayType (..), readTeX, writePandoc)  import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap -import Control.Monad (guard, mplus, mzero, void, when) +import Control.Monad (guard, mplus, mzero, unless, void, when)  import Control.Monad.Trans (lift)  import Data.Char (isAlphaNum, isSpace)  import Data.List (intersperse) @@ -63,7 +63,7 @@ import Prelude hiding (sequence)  --  recordAnchorId :: PandocMonad m => String -> OrgParser m ()  recordAnchorId i = updateState $ \s -> -  s{ orgStateAnchorIds = i : (orgStateAnchorIds s) } +  s{ orgStateAnchorIds = i : orgStateAnchorIds s }  pushToInlineCharStack :: PandocMonad m => Char -> OrgParser m ()  pushToInlineCharStack c = updateState $ \s -> @@ -184,7 +184,7 @@ cite = try $ berkeleyCite <|> do                 , orgRefCite                 , berkeleyTextualCite                 ] -  return $ (flip B.cite (B.text raw)) <$> cs +  return $ flip B.cite (B.text raw) <$> cs  -- | A citation in Pandoc Org-mode style (@[prefix \@citekey suffix]@).  pandocOrgCite :: PandocMonad m => OrgParser m (F [Citation]) @@ -209,7 +209,7 @@ normalOrgRefCite = try $ do    orgRefCiteList :: PandocMonad m => CitationMode -> OrgParser m (F Citation)    orgRefCiteList citeMode = try $ do      key <- orgRefCiteKey -    returnF $ Citation +    returnF Citation       { citationId      = key       , citationPrefix  = mempty       , citationSuffix  = mempty @@ -232,11 +232,11 @@ berkeleyCite = try $ do      return $        if parens        then toCite -           . maybe id (\p -> alterFirst (prependPrefix p)) prefix -           . maybe id (\s -> alterLast  (appendSuffix  s)) suffix +           . maybe id (alterFirst . prependPrefix) prefix +           . maybe id (alterLast . appendSuffix) suffix             $ citationList        else maybe mempty (<> " ") prefix -             <> (toListOfCites $ map toInTextMode citationList) +             <> toListOfCites (map toInTextMode citationList)               <> maybe mempty (", " <>) suffix   where     toCite :: [Citation] -> Inlines @@ -250,7 +250,7 @@ berkeleyCite = try $ do     alterFirst, alterLast :: (a -> a) -> [a] -> [a]     alterFirst _ []     = [] -   alterFirst f (c:cs) = (f c):cs +   alterFirst f (c:cs) = f c : cs     alterLast  f = reverse . alterFirst f . reverse     prependPrefix, appendSuffix :: Inlines -> Citation -> Citation @@ -271,7 +271,7 @@ berkeleyCitationList = try $ do    skipSpaces    commonPrefix <- optionMaybe (try $ citationListPart <* char ';')    citations    <- citeList -  commonSuffix <- optionMaybe (try $ citationListPart) +  commonSuffix <- optionMaybe (try citationListPart)    char ']'    return (BerkeleyCitationList parens      <$> sequence commonPrefix @@ -344,7 +344,7 @@ orgRefCiteKey =        isCiteKeySpecialChar c = c `elem` citeKeySpecialChars        isCiteKeyChar c = isAlphaNum c || isCiteKeySpecialChar c -  in try $ many1Till (satisfy $ isCiteKeyChar) +  in try $ many1Till (satisfy isCiteKeyChar)             $ try . lookAhead $ do                 many . satisfy $ isCiteKeySpecialChar                 satisfy $ not . isCiteKeyChar @@ -374,15 +374,16 @@ citation = try $ do    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 x +      , citationSuffix  = B.toList y +      , citationMode    = if suppress_author +                          then SuppressAuthor +                          else NormalCitation +      , citationNoteNum = 0 +      , citationHash    = 0 +      }   where     prefix = trimInlinesF . mconcat <$>              manyTill inline (char ']' <|> (']' <$ lookAhead citeKey)) @@ -404,7 +405,7 @@ inlineNote = try $ do    ref <- many alphaNum    char ':'    note <- fmap B.para . trimInlinesF . mconcat <$> many1Till inline (char ']') -  when (not $ null ref) $ +  unless (null ref) $         addToNotesTable ("fn:" ++ ref, note)    return $ B.note <$> note @@ -780,7 +781,7 @@ notAfterForbiddenBorderChar = do  -- | Read a sub- or superscript expression  subOrSuperExpr :: PandocMonad m => OrgParser m (F Inlines)  subOrSuperExpr = try $ -  choice [ id                   <$> charsInBalanced '{' '}' (noneOf "\n\r") +  choice [ charsInBalanced '{' '}' (noneOf "\n\r")           , enclosing ('(', ')') <$> charsInBalanced '(' ')' (noneOf "\n\r")           , simpleSubOrSuperString           ] >>= parseFromString (mconcat <$> many inline) @@ -818,7 +819,7 @@ inlineLaTeX = try $ do                      enableExtension Ext_raw_tex (readerExtensions def) } }     texMathToPandoc :: String -> Maybe [Inline] -   texMathToPandoc cs = (maybeRight $ readTeX cs) >>= writePandoc DisplayInline +   texMathToPandoc cs = maybeRight (readTeX cs) >>= writePandoc DisplayInline  maybeRight :: Either a b -> Maybe b  maybeRight = either (const Nothing) Just @@ -869,21 +870,19 @@ macro = try $ do    eoa = string ")}}}"  smart :: PandocMonad m => OrgParser m (F Inlines) -smart = do -  doubleQuoted <|> singleQuoted <|> -    choice (map (return <$>) [orgApostrophe, orgDash, orgEllipses]) +smart = choice [doubleQuoted, singleQuoted, orgApostrophe, orgDash, orgEllipses]    where      orgDash = do        guardOrSmartEnabled =<< getExportSetting exportSpecialStrings -      dash <* updatePositions '-' +      pure <$> dash <* updatePositions '-'      orgEllipses = do        guardOrSmartEnabled =<< getExportSetting exportSpecialStrings -      ellipses <* updatePositions '.' +      pure <$> ellipses <* updatePositions '.'      orgApostrophe = do        guardEnabled Ext_smart        (char '\'' <|> char '\8217') <* updateLastPreCharPos                                     <* updateLastForbiddenCharPos -      return (B.str "\x2019") +      returnF (B.str "\x2019")  guardOrSmartEnabled :: PandocMonad m => Bool -> OrgParser m ()  guardOrSmartEnabled b = do @@ -908,6 +907,9 @@ doubleQuoted = try $ do    doubleQuoteStart    updatePositions '"'    contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) -  (withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return -       (fmap B.doubleQuoted . trimInlinesF $ contents)) -   <|> (return $ return (B.str "\8220") <> contents) +  let doubleQuotedContent = withQuoteContext InDoubleQuote $ do +        doubleQuoteEnd +        updateLastForbiddenCharPos +        return . fmap B.doubleQuoted . trimInlinesF $ contents +  let leftQuoteAndContent = return $ pure (B.str "\8220") <> contents +  doubleQuotedContent <|> leftQuoteAndContent diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 33c212bca..a87042871 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -84,7 +84,7 @@ metaKey = map toLower <$> many1 (noneOf ": \n\r")                        <*  char ':'                        <*  skipSpaces -metaValue :: PandocMonad m => String -> OrgParser m (String, (F MetaValue)) +metaValue :: PandocMonad m => String -> OrgParser m (String, F MetaValue)  metaValue key =    let inclKey = "header-includes"    in case key of @@ -111,7 +111,7 @@ metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline  metaInlinesCommaSeparated :: PandocMonad m => OrgParser m (F MetaValue)  metaInlinesCommaSeparated = do -  itemStrs <- (many1 (noneOf ",\n")) `sepBy1` (char ',') +  itemStrs <- many1 (noneOf ",\n") `sepBy1` char ','    newline    items <- mapM (parseFromString inlinesTillNewline . (++ "\n")) itemStrs    let toMetaInlines = MetaInlines . B.toList @@ -163,7 +163,7 @@ addLinkFormat key formatter = updateState $ \s ->    let fs = orgStateLinkFormatters s    in s{ orgStateLinkFormatters = M.insert key formatter fs } -parseLinkFormat :: Monad m => OrgParser m ((String, String -> String)) +parseLinkFormat :: Monad m => OrgParser m (String, String -> String)  parseLinkFormat = try $ do    linkType <- (:) <$> letter <*> many (alphaNum <|> oneOf "-_") <* skipSpaces    linkSubst <- parseFormat @@ -172,8 +172,7 @@ parseLinkFormat = try $ do  -- | An ad-hoc, single-argument-only implementation of a printf-style format  -- parser.  parseFormat :: Monad m => OrgParser m (String -> String) -parseFormat = try $ do -  replacePlain <|> replaceUrl <|> justAppend +parseFormat = try $ replacePlain <|> replaceUrl <|> justAppend   where     -- inefficient, but who cares     replacePlain = try $ (\x -> concat . flip intersperse x) diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 4520a5552..6a78ce276 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -1,5 +1,4 @@  {-# LANGUAGE FlexibleInstances          #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-}  {-# LANGUAGE MultiParamTypeClasses      #-}  {-  Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index d9414319a..952082ec1 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -56,7 +56,7 @@ cleanLinkString s =      '.':'/':_              -> Just s                 -- relative path      '.':'.':'/':_          -> Just s                 -- relative path      -- Relative path or URL (file schema) -    'f':'i':'l':'e':':':s' -> Just $ if ("//" `isPrefixOf` s') then s else s' +    'f':'i':'l':'e':':':s' -> Just $ if "//" `isPrefixOf` s' then s else s'      _                      | isUrl s            -> Just s                 -- URL      _                      -> Nothing   where | 
