diff options
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 13 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 2 | 
2 files changed, 10 insertions, 5 deletions
| diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index db1e70ea0..5a50a8f34 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1581,8 +1581,8 @@ inlineLaTeX = try $ do     parseAsMathMLSym :: String -> Maybe Inlines     parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs) -    -- dropWhileEnd would be nice here, but it's not available before base 4.5 -    where clean = reverse . dropWhile (`elem` ("{}" :: String)) . reverse . drop 1 +    -- drop initial backslash and any trailing "{}" +    where clean = dropWhileEnd (`elem` ("{}" :: String)) . drop 1     state :: ParserState     state = def{ stateOptions = def{ readerParseRaw = True }} @@ -1598,13 +1598,18 @@ inlineLaTeXCommand = try $ do    rest <- getInput    case runParser rawLaTeXInline def "source" rest of      Right (RawInline _ cs) -> do -      -- drop any trailing whitespace, those should not be part of the command -      let cmdNoSpc = takeWhile (not . isSpace) $ cs +      -- drop any trailing whitespace, those are not be part of the command as +      -- far as org mode is concerned. +      let cmdNoSpc = dropWhileEnd isSpace cs        let len = length cmdNoSpc        count len anyChar        return cmdNoSpc      _ -> mzero +-- Taken from Data.OldList. +dropWhileEnd :: (a -> Bool) -> [a] -> [a] +dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) [] +  smart :: OrgParser (F Inlines)  smart = do    getOption readerSmart >>= guard diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 20086ed19..e57a6fc11 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -170,7 +170,7 @@ blockToOrg (Table caption' _ _ headers rows) =  do         map ((+2) . numChars) $ transpose (headers' : rawRows)    -- FIXME: Org doesn't allow blocks with height more than 1.    let hpipeBlocks blocks = hcat [beg, middle, end] -        where h      = maximum (map height blocks) +        where h      = maximum (1 : map height blocks)                sep'   = lblock 3 $ vcat (map text $ replicate h " | ")                beg    = lblock 2 $ vcat (map text $ replicate h "| ")                end    = lblock 2 $ vcat (map text $ replicate h " |") | 
