diff options
-rw-r--r-- | .editorconfig | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 64 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 25 | ||||
-rw-r--r-- | tests/writer.org | 2 |
5 files changed, 84 insertions, 13 deletions
diff --git a/.editorconfig b/.editorconfig index 9c562bd1f..5f40572b0 100644 --- a/.editorconfig +++ b/.editorconfig @@ -10,3 +10,7 @@ trim_trailing_whitespace = true [*.{markdown,md}] trim_trailing_whitespace = false + +[tests/*] +insert_final_newline = false +trim_trailing_whitespace = false diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index ceac69367..bda0b0262 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -37,6 +37,7 @@ import Text.Pandoc.Parsing hiding (newline, orderedListMarker, updateL import Text.Pandoc.Shared (compactify') import Control.Applicative (pure, (<$>), (<$), (<*>), (<*), (*>), (<**>)) +import Control.Arrow ((***)) import Control.Monad (guard, when) import Data.Char (toLower) import Data.Default @@ -44,9 +45,6 @@ import Data.List (foldl', isPrefixOf, isSuffixOf) import Data.Maybe (listToMaybe, fromMaybe) import Data.Monoid (mconcat, mempty, mappend) --- Ignore HLint warnings to use String instead of [Char] -{-# ANN module ("HLint: ignore Use String" :: String) #-} - -- | Parse org-mode string and return a Pandoc document. readOrg :: ReaderOptions -- ^ Reader options -> String -- ^ String to parse (assuming @'\n'@ line endings) @@ -158,6 +156,7 @@ block = choice [ mempty <$ blanklines , orgBlock , example , drawer + , figure , specialLine , header , hline @@ -252,6 +251,43 @@ drawerEnd = try $ skipSpaces *> stringAnyCase ":END:" <* skipSpaces <* newline +-- +-- Figures +-- + +-- Figures (Image on a line by itself, preceded by name and/or caption) +figure :: OrgParser Blocks +figure = try $ do + (tit, cap) <- (maybe mempty withFigPrefix *** fromMaybe mempty) + <$> nameAndOrCaption + src <- skipSpaces *> selfTarget <* skipSpaces <* newline + guard (isImageFilename src) + return . B.para $ B.image src tit cap + where withFigPrefix cs = if "fig:" `isPrefixOf` cs + then cs + else "fig:" ++ cs + +nameAndOrCaption :: OrgParser (Maybe String, Maybe Inlines) +nameAndOrCaption = try $ nameFirst <|> captionFirst + where + nameFirst = try $ do + n <- name + c <- optionMaybe caption + return (Just n, c) + captionFirst = try $ do + c <- caption + n <- optionMaybe name + return (n, Just c) + +caption :: OrgParser Inlines +caption = try $ annotation "CAPTION" *> inlinesTillNewline + +name :: OrgParser String +name = try $ annotation "NAME" *> skipSpaces *> manyTill anyChar newline + +annotation :: String -> OrgParser String +annotation ann = try $ metaLineStart *> stringAnyCase ann <* char ':' + -- Comments, Options and Metadata specialLine :: OrgParser Blocks specialLine = try $ metaLine <|> commentLine @@ -277,7 +313,7 @@ declarationLine = try $ do return mempty metaValue :: OrgParser MetaValue -metaValue = MetaInlines . B.toList . trimInlines <$> restOfLine +metaValue = MetaInlines . B.toList <$> inlinesTillNewline metaKey :: OrgParser String metaKey = map toLower <$> many1 (noneOf ": \n\r") @@ -288,7 +324,7 @@ metaKey = map toLower <$> many1 (noneOf ": \n\r") header :: OrgParser Blocks header = try $ B.header <$> headerStart - <*> (trimInlines <$> restOfLine) + <*> inlinesTillNewline headerStart :: OrgParser Int headerStart = try $ @@ -424,13 +460,10 @@ setAligns aligns t = t{ orgTableAlignments = aligns } -- Paragraphs or Plain text paraOrPlain :: OrgParser Blocks paraOrPlain = try $ - trimInlines . mconcat - <$> many1 inline - <**> option B.plain - (try $ newline *> pure B.para) + parseInlines <**> option B.plain (try $ newline *> pure B.para) -restOfLine :: OrgParser Inlines -restOfLine = mconcat <$> manyTill inline newline +inlinesTillNewline :: OrgParser Inlines +inlinesTillNewline = trimInlines . mconcat <$> manyTill inline newline -- @@ -506,6 +539,7 @@ anyLineNewline = (++ "\n") <$> anyLine inline :: OrgParser Inlines inline = choice [ whitespace + , linebreak , link , str , endline @@ -523,6 +557,8 @@ inline = ] <* (guard =<< newlinesCountWithinLimits) <?> "inline" +parseInlines :: OrgParser Inlines +parseInlines = trimInlines . mconcat <$> many1 inline -- treat these as potentially non-text when parsing inline: specialChars :: [Char] @@ -535,6 +571,9 @@ whitespace = B.space <$ skipMany1 spaceChar <* updateLastForbiddenCharPos <?> "whitespace" +linebreak :: OrgParser Inlines +linebreak = try $ B.linebreak <$ string "\\\\" <* skipSpaces <* newline + str :: OrgParser Inlines str = B.str <$> many1 (noneOf $ specialChars ++ "\n\r ") <* updateLastStrPos @@ -580,6 +619,9 @@ selflinkOrImage = try $ do then B.image src "" "" else B.link src "" (B.str src) +selfTarget :: OrgParser String +selfTarget = try $ char '[' *> linkTarget <* char ']' + linkTarget :: OrgParser String linkTarget = enclosed (char '[') (char ']') (noneOf "\n\r]") diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index d318c5f6a..58a5729e7 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -271,7 +271,7 @@ inlineToOrg (Math t str) = do else "$$" <> text str <> "$$" inlineToOrg (RawInline f str) | f == "tex" || f == "latex" = return $ text str inlineToOrg (RawInline _ _) = return empty -inlineToOrg (LineBreak) = return cr -- there's no line break in Org +inlineToOrg (LineBreak) = return (text "\\\\" <> cr) inlineToOrg Space = return space inlineToOrg (Link txt (src, _)) = do case txt of diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index 49130f0ab..f39bd7992 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -94,6 +94,10 @@ tests = "a_{n+1}" =?> para (str "a" <> subscript "n+1") + , "Linebreak" =: + "line \\\\ \nbreak" =?> + para ("line" <> linebreak <> "break") + , "Markup-chars not occuring on word break are symbols" =: unlines [ "this+that+ +so+on" , "seven*eight* nine*" @@ -377,6 +381,27 @@ tests = code' = "main = putStrLn greeting\n" ++ " where greeting = \"moin\"\n" in codeBlockWith attr' code' + + , "Figure" =: + unlines [ "#+caption: A very courageous man." + , "#+name: goodguy" + , "[[edward.jpg]]" + ] =?> + para (image "edward.jpg" "fig:goodguy" "A very courageous man.") + + , "Unnamed figure" =: + unlines [ "#+caption: A great whistleblower." + , "[[snowden.png]]" + ] =?> + para (image "snowden.png" "" "A great whistleblower.") + + , "Figure with `fig:` prefix in name" =: + unlines [ "#+caption: Used as a metapher in evolutionary biology." + , "#+name: fig:redqueen" + , "[[the-red-queen.jpg]]" + ] =?> + para (image "the-red-queen.jpg" "fig:redqueen" + "Used as a metapher in evolutionary biology.") ] , testGroup "Lists" $ diff --git a/tests/writer.org b/tests/writer.org index 85016f352..524d49305 100644 --- a/tests/writer.org +++ b/tests/writer.org @@ -42,7 +42,7 @@ item. Here's one with a bullet. * criminey. -There should be a hard line break +There should be a hard line break\\ here. -------------- |