From 8f8f0f8a603a75ea56068f65ef6e13c2c66a8402 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Fri, 23 Feb 2018 22:07:30 +0300 Subject: Muse writer: don't indent nested definition lists --- src/Text/Pandoc/Writers/Muse.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 7f53e202d..b4eb19ef6 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -207,7 +207,9 @@ blockToMuse (BulletList items) = do return $ hang 2 "- " contents blockToMuse (DefinitionList items) = do contents <- mapM definitionListItemToMuse items - return $ cr $$ nest 1 (vcat contents) $$ blankline + -- ensure that sublists have preceding blank line + topLevel <- gets stTopLevel + return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where definitionListItemToMuse :: PandocMonad m => ([Inline], [[Block]]) -> StateT WriterState m Doc -- cgit v1.2.3 From 1d57f7a641e9c66d56cab20905a602202336fbad Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Feb 2018 14:26:11 +0300 Subject: Muse writer: remove empty strings during inline normalization --- src/Text/Pandoc/Writers/Muse.hs | 2 ++ test/Tests/Writers/Muse.hs | 1 + 2 files changed, 3 insertions(+) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index b4eb19ef6..4086bdd9c 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -299,6 +299,8 @@ conditionalEscapeString s = else s normalizeInlineList :: [Inline] -> [Inline] +normalizeInlineList (x : Str "" : xs) + = normalizeInlineList (x:xs) normalizeInlineList (Emph x1 : Emph x2 : ils) = normalizeInlineList $ Emph (x1 ++ x2) : ils normalizeInlineList (Strong x1 : Strong x2 : ils) diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 7aee36217..bbf833563 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -319,6 +319,7 @@ tests = [ testGroup "block elements" , "escape tag" =: code "foo = bar baz" =?> "foo = bar</code> baz" , "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "foobar" , "normalization" =: code " code "de>" =?> "</code>" + , "normalization with empty string" =: code " str "" <> code "de>" =?> "</code>" ] , testGroup "spaces" [ "space" =: text "a" <> space <> text "b" =?> "a b" -- cgit v1.2.3 From 8b1630aae029a0c4ce6e6dc881d3e11d0ca7e9ce Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Feb 2018 14:42:43 +0300 Subject: Muse writer: change verse markup Use "> " instead of tag --- src/Text/Pandoc/Writers/Muse.hs | 11 ++--------- test/Tests/Writers/Muse.hs | 8 +++----- 2 files changed, 5 insertions(+), 14 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 4086bdd9c..314e7a5c1 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -156,15 +156,8 @@ blockToMuse (Para inlines) = do contents <- inlineListToMuse inlines return $ contents <> blankline blockToMuse (LineBlock lns) = do - let splitStanza [] = [] - splitStanza xs = case break (== mempty) xs of - (l, []) -> [l] - (l, _:r) -> l : splitStanza r - let joinWithLinefeeds = nowrap . mconcat . intersperse cr - let joinWithBlankLines = mconcat . intersperse blankline - let prettyfyStanza ls = joinWithLinefeeds <$> mapM inlineListToMuse ls - contents <- joinWithBlankLines <$> mapM prettyfyStanza (splitStanza lns) - return $ blankline $$ "" $$ contents $$ "" <> blankline + lns' <- mapM inlineListToMuse lns + return $ nowrap $ vcat (map ((text "> ") <>) lns') <> blankline blockToMuse (CodeBlock (_,_,_) str) = return $ "" $$ text str $$ "" $$ blankline blockToMuse (RawBlock (Format format) str) = diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index bbf833563..a5a6986f2 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -34,11 +34,9 @@ tests = [ testGroup "block elements" ] ] , "line block" =: lineBlock [text "Foo", text "bar", text "baz"] - =?> unlines [ "" - , "Foo" - , "bar" - , "baz" - , "" + =?> unlines [ "> Foo" + , "> bar" + , "> baz" ] , "code block" =: codeBlock "int main(void) {\n\treturn 0;\n}" =?> unlines [ "" -- cgit v1.2.3 From 9dbd59a7c120eee9a0bbe292a05dd144987fa0a0 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Fri, 2 Mar 2018 01:39:16 +0300 Subject: Muse writer: join strings during inline normalization --- src/Text/Pandoc/Writers/Muse.hs | 2 ++ test/Tests/Writers/Muse.hs | 1 + 2 files changed, 3 insertions(+) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 314e7a5c1..bf1f267fd 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -294,6 +294,8 @@ conditionalEscapeString s = normalizeInlineList :: [Inline] -> [Inline] normalizeInlineList (x : Str "" : xs) = normalizeInlineList (x:xs) +normalizeInlineList (Str x1 : Str x2 : xs) + = normalizeInlineList $ Str (x1 ++ x2) : xs normalizeInlineList (Emph x1 : Emph x2 : ils) = normalizeInlineList $ Emph (x1 ++ x2) : ils normalizeInlineList (Strong x1 : Strong x2 : ils) diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index a5a6986f2..0b8a08258 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -297,6 +297,7 @@ tests = [ testGroup "block elements" , "escape hash to avoid accidental anchors" =: text "#foo bar" =?> "#foo bar" , "escape definition list markers" =: str "::" =?> "::" + , "normalize strings before escaping" =: fromList [Str ":", Str ":"] =?> "::" -- We don't want colons to be escaped if they can't be confused -- with definition list item markers. , "do not escape colon" =: str ":" =?> ":" -- cgit v1.2.3 From 991b57733c508634d6093e2aeb2ffb3feec13c42 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Fri, 2 Mar 2018 19:51:54 +0300 Subject: hlint Muse reader and writer --- src/Text/Pandoc/Readers/Muse.hs | 4 ++-- src/Text/Pandoc/Writers/Muse.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index c083933ff..8bb087629 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -401,7 +401,7 @@ exampleTag = try $ do return $ return $ B.codeBlockWith attr $ rchop $ intercalate "\n" $ dropSpacePrefix $ splitOn "\n" $ lchop contents literalTag :: PandocMonad m => MuseParser m (F Blocks) -literalTag = do +literalTag = (return . rawBlock) <$> htmlBlock "literal" where -- FIXME: Emacs Muse inserts without style into all output formats, but we assume HTML @@ -878,7 +878,7 @@ codeTag = do return $ return $ B.codeWith attrs content inlineLiteralTag :: PandocMonad m => MuseParser m (F Inlines) -inlineLiteralTag = do +inlineLiteralTag = (return . rawInline) <$> htmlElement "literal" where -- FIXME: Emacs Muse inserts without style into all output formats, but we assume HTML diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index bf1f267fd..ad67e489d 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -157,7 +157,7 @@ blockToMuse (Para inlines) = do return $ contents <> blankline blockToMuse (LineBlock lns) = do lns' <- mapM inlineListToMuse lns - return $ nowrap $ vcat (map ((text "> ") <>) lns') <> blankline + return $ nowrap $ vcat (map (text "> " <>) lns') <> blankline blockToMuse (CodeBlock (_,_,_) str) = return $ "" $$ text str $$ "" $$ blankline blockToMuse (RawBlock (Format format) str) = -- cgit v1.2.3 From 7da6e4390cb6d812b67dca6720bb56f3963c05d5 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 5 Mar 2018 19:38:11 +0300 Subject: Muse writer: expand math before inline list normalization --- src/Text/Pandoc/Writers/Muse.hs | 16 +++++++++++++--- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 14 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index ad67e489d..1f6006b2e 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -291,6 +291,14 @@ conditionalEscapeString s = then escapeString s else s +-- Expand Math before normalizing inline list +preprocessInlineList :: PandocMonad m + => [Inline] + -> m [Inline] +preprocessInlineList (Math t str:xs) = (++ xs) <$> texMathToInlines t str +preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs +preprocessInlineList [] = return [] + normalizeInlineList :: [Inline] -> [Inline] normalizeInlineList (x : Str "" : xs) = normalizeInlineList (x:xs) @@ -327,7 +335,9 @@ fixNotes (x:xs) = x : fixNotes xs inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc -inlineListToMuse lst = hcat <$> mapM inlineToMuse (fixNotes $ normalizeInlineList lst) +inlineListToMuse lst = do + lst' <- preprocessInlineList lst + hcat <$> mapM inlineToMuse (fixNotes $ normalizeInlineList lst') -- | Convert Pandoc inline element to Muse. inlineToMuse :: PandocMonad m @@ -363,8 +373,8 @@ inlineToMuse (Quoted DoubleQuote lst) = do inlineToMuse (Cite _ lst) = inlineListToMuse lst inlineToMuse (Code _ str) = return $ "" <> text (substitute "" "</code>" str) <> "" -inlineToMuse (Math t str) = - lift (texMathToInlines t str) >>= inlineListToMuse +inlineToMuse Math{} = + fail "Math should be expanded before normalization" inlineToMuse (RawInline (Format f) str) = return $ " text f <> "\">" <> text str <> "" inlineToMuse LineBreak = return $ "
" <> cr diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 0b8a08258..df02236ac 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -332,6 +332,7 @@ tests = [ testGroup "block elements" [ "inline math" =: math "2^3" =?> "23" , "display math" =: displayMath "2^3" =?> "23" , "multiple letters in inline math" =: math "abc" =?> "abc" + , "expand math before normalization" =: math "[" <> str "2]" =?> "[2]" ] , "raw inline" =: rawInline "html" "marked text" -- cgit v1.2.3 From 31b4387a6b53fb543fa6139e6174ad2e2c7bb5e9 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 6 Mar 2018 12:53:19 +0300 Subject: Muse writer: fix math expansion for more than one expression per paragraph --- src/Text/Pandoc/Writers/Muse.hs | 2 +- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 1f6006b2e..404ebf7bc 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -295,7 +295,7 @@ conditionalEscapeString s = preprocessInlineList :: PandocMonad m => [Inline] -> m [Inline] -preprocessInlineList (Math t str:xs) = (++ xs) <$> texMathToInlines t str +preprocessInlineList (Math t str:xs) = (++) <$> texMathToInlines t str <*> preprocessInlineList xs preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs preprocessInlineList [] = return [] diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index df02236ac..7aec8122a 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -333,6 +333,7 @@ tests = [ testGroup "block elements" , "display math" =: displayMath "2^3" =?> "23" , "multiple letters in inline math" =: math "abc" =?> "abc" , "expand math before normalization" =: math "[" <> str "2]" =?> "[2]" + , "multiple math expressions inside one inline list" =: math "5_4" <> text ", " <> displayMath "3^2" =?> "54, 32" ] , "raw inline" =: rawInline "html" "marked text" -- cgit v1.2.3 From 1b1b6f02d59626fac591e4ed4a2286c6effca6d2 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 15:19:36 +0300 Subject: Muse writer: escape "-" to avoid creating bullet lists --- src/Text/Pandoc/Writers/Muse.hs | 3 ++- test/Tests/Writers/Muse.hs | 9 +++++++++ test/writer.muse | 2 +- 3 files changed, 12 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 404ebf7bc..ea46507db 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -287,7 +287,8 @@ conditionalEscapeString s = if any (`elem` ("#*<=>[]|" :: String)) s || "::" `isInfixOf` s || "----" `isInfixOf` s || - "~~" `isInfixOf` s + "~~" `isInfixOf` s || + "-" == s then escapeString s else s diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 7aec8122a..ab5eaa205 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -301,6 +301,15 @@ tests = [ testGroup "block elements" -- We don't want colons to be escaped if they can't be confused -- with definition list item markers. , "do not escape colon" =: str ":" =?> ":" + , "escape - to avoid accidental unordered lists" =: text " - foo" =?> " - foo" + , "escape - inside a list to avoid accidental nested unordered lists" =: + bulletList [ (para $ text "foo") <> + (para $ text "- bar") + ] =?> + unlines [ " - foo" + , "" + , " - bar" + ] ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" diff --git a/test/writer.muse b/test/writer.muse index 6cb766955..5db3871a1 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -594,7 +594,7 @@ Bang: ! Plus: + -Minus: - +Minus: - ---- -- cgit v1.2.3 From 39b31ef3cb6f227bc17f923cc00597ca70298820 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 16:25:15 +0300 Subject: Muse writer: remove empty Str from the beginning of inline lists during normalization --- src/Text/Pandoc/Writers/Muse.hs | 2 ++ 1 file changed, 2 insertions(+) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index ea46507db..6cdd3e182 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -301,6 +301,8 @@ preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs preprocessInlineList [] = return [] normalizeInlineList :: [Inline] -> [Inline] +normalizeInlineList (Str "" : xs) + = normalizeInlineList xs normalizeInlineList (x : Str "" : xs) = normalizeInlineList (x:xs) normalizeInlineList (Str x1 : Str x2 : xs) -- cgit v1.2.3 From f8e255053de09786c6c251e38387663750ddd3ac Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 16:27:56 +0300 Subject: Muse writer: write empty inline lists as --- src/Text/Pandoc/Writers/Muse.hs | 6 ++++-- test/Tests/Writers/Muse.hs | 9 +++++++++ 2 files changed, 13 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 6cdd3e182..7a9bc8130 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -339,8 +339,10 @@ inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc inlineListToMuse lst = do - lst' <- preprocessInlineList lst - hcat <$> mapM inlineToMuse (fixNotes $ normalizeInlineList lst') + lst' <- normalizeInlineList <$> preprocessInlineList lst + if null lst' + then pure "" + else hcat <$> mapM inlineToMuse (fixNotes lst') -- | Convert Pandoc inline element to Muse. inlineToMuse :: PandocMonad m diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index ab5eaa205..68eb9759f 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -101,6 +101,15 @@ tests = [ testGroup "block elements" , " :: second description" , " second definition :: third description" ] + , "definition list with empty term" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (mempty, [plain $ text "second description"]) + , (str "", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " :: second description" + , " :: third description" + ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" -- cgit v1.2.3 From f8608b418afcb1cfe8ccb55abf31f33f7bc7efb3 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 19:11:03 +0300 Subject: Muse writer: expand Cite before list normalization --- src/Text/Pandoc/Writers/Muse.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 7a9bc8130..156958ab7 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -292,11 +292,16 @@ conditionalEscapeString s = then escapeString s else s --- Expand Math before normalizing inline list +-- Expand Math and Cite before normalizing inline list preprocessInlineList :: PandocMonad m => [Inline] -> m [Inline] preprocessInlineList (Math t str:xs) = (++) <$> texMathToInlines t str <*> preprocessInlineList xs +-- Amusewiki does not support tag, +-- and Emacs Muse citation support is limited +-- (https://www.gnu.org/software/emacs-muse/manual/html_node/Citations.html#Citation) +-- so just fallback to expanding inlines. +preprocessInlineList (Cite _ lst:xs) = (lst ++) <$> preprocessInlineList xs preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs preprocessInlineList [] = return [] @@ -371,11 +376,8 @@ inlineToMuse (Quoted SingleQuote lst) = do inlineToMuse (Quoted DoubleQuote lst) = do contents <- inlineListToMuse lst return $ "“" <> contents <> "”" --- Amusewiki does not support tag, --- and Emacs Muse citation support is limited --- (https://www.gnu.org/software/emacs-muse/manual/html_node/Citations.html#Citation) --- so just fallback to expanding inlines. -inlineToMuse (Cite _ lst) = inlineListToMuse lst +inlineToMuse (Cite {}) = + fail "Citations should be expanded before normalization" inlineToMuse (Code _ str) = return $ "" <> text (substitute "" "</code>" str) <> "" inlineToMuse Math{} = -- cgit v1.2.3 From ff8e59a17412e7a083ab5ce53a1af2db59025a44 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 19:11:27 +0300 Subject: Muse writer: output smallcaps as emphasis --- src/Text/Pandoc/Writers/Muse.hs | 2 +- test/Tests/Writers/Muse.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 156958ab7..28cfb0ef4 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -369,7 +369,7 @@ inlineToMuse (Superscript lst) = do inlineToMuse (Subscript lst) = do contents <- inlineListToMuse lst return $ "" <> contents <> "" -inlineToMuse (SmallCaps lst) = inlineListToMuse lst +inlineToMuse (SmallCaps lst) = inlineToMuse (Emph lst) inlineToMuse (Quoted SingleQuote lst) = do contents <- inlineListToMuse lst return $ "‘" <> contents <> "’" diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 68eb9759f..bbcb3dc61 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -327,7 +327,7 @@ tests = [ testGroup "block elements" ] , "superscript" =: superscript (text "foo") =?> "foo" , "subscript" =: subscript (text "foo") =?> "foo" - , "smallcaps" =: smallcaps (text "foo") =?> "foo" + , "smallcaps" =: smallcaps (text "foo") =?> "foo" , "single quoted" =: singleQuoted (text "foo") =?> "‘foo’" , "double quoted" =: doubleQuoted (text "foo") =?> "“foo”" -- Cite is trivial -- cgit v1.2.3 From 1884ee60838ffeac090cafc9cf7fe2e44ad33636 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 7 Mar 2018 20:10:19 +0300 Subject: Muse writer: replace smallcaps with emphasis before normalization --- src/Text/Pandoc/Writers/Muse.hs | 9 +++++++-- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 8 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 28cfb0ef4..daffa2d07 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -305,6 +305,10 @@ preprocessInlineList (Cite _ lst:xs) = (lst ++) <$> preprocessInlineList xs preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs preprocessInlineList [] = return [] +replaceSmallCaps :: Inline -> Inline +replaceSmallCaps (SmallCaps lst) = Emph lst +replaceSmallCaps x = x + normalizeInlineList :: [Inline] -> [Inline] normalizeInlineList (Str "" : xs) = normalizeInlineList xs @@ -344,7 +348,7 @@ inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc inlineListToMuse lst = do - lst' <- normalizeInlineList <$> preprocessInlineList lst + lst' <- normalizeInlineList <$> preprocessInlineList (map replaceSmallCaps lst) if null lst' then pure "" else hcat <$> mapM inlineToMuse (fixNotes lst') @@ -369,7 +373,8 @@ inlineToMuse (Superscript lst) = do inlineToMuse (Subscript lst) = do contents <- inlineListToMuse lst return $ "" <> contents <> "" -inlineToMuse (SmallCaps lst) = inlineToMuse (Emph lst) +inlineToMuse (SmallCaps {}) = + fail "SmallCaps should be expanded before normalization" inlineToMuse (Quoted SingleQuote lst) = do contents <- inlineListToMuse lst return $ "‘" <> contents <> "’" diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index bbcb3dc61..509c20401 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -328,6 +328,7 @@ tests = [ testGroup "block elements" , "superscript" =: superscript (text "foo") =?> "foo" , "subscript" =: subscript (text "foo") =?> "foo" , "smallcaps" =: smallcaps (text "foo") =?> "foo" + , "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "foobar" , "single quoted" =: singleQuoted (text "foo") =?> "‘foo’" , "double quoted" =: doubleQuoted (text "foo") =?> "“foo”" -- Cite is trivial -- cgit v1.2.3 From 19fd98e452ee1f7be902735ac76500306672f2e7 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 12 Mar 2018 01:40:23 +0300 Subject: Muse writer: support spans with anchors --- src/Text/Pandoc/Writers/Muse.hs | 10 +++++++--- test/Tests/Writers/Muse.hs | 6 +++++- 2 files changed, 12 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index daffa2d07..8a8217d94 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -424,7 +424,11 @@ inlineToMuse (Note contents) = do modify $ \st -> st { stNotes = contents:notes } let ref = show $ length notes + 1 return $ "[" <> text ref <> "]" -inlineToMuse (Span (_,name:_,_) inlines) = do +inlineToMuse (Span (anchor,names,_) inlines) = do contents <- inlineListToMuse inlines - return $ " text name <> "\">" <> contents <> "" -inlineToMuse (Span _ lst) = inlineListToMuse lst + let anchorDoc = if null anchor + then mempty + else text ('#':anchor) <> space + return $ anchorDoc <> if null names + then contents + else " text (head names) <> "\">" <> contents <> "" diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 509c20401..b86dee5e1 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -380,8 +380,12 @@ tests = [ testGroup "block elements" , "" , "[1] Foo" ] - , "span" =: spanWith ("",["foobar"],[]) (str "Some text") + , "span with class" =: spanWith ("",["foobar"],[]) (text "Some text") =?> "Some text" + , "span with anchor" =: spanWith ("anchor", [], []) (text "Foo bar") + =?> "#anchor Foo bar" + , "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar") + =?> "#anchor bar" , testGroup "combined" [ "emph word before" =: para (text "foo" <> emph (text "bar")) =?> -- cgit v1.2.3 From dfa1dc164a15389e00c86b8d97d71646827a74cf Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 17 Mar 2018 22:00:55 -0700 Subject: hlint fixes. --- src/Text/Pandoc/ImageSize.hs | 10 +++++----- src/Text/Pandoc/Lua/Util.hs | 2 +- src/Text/Pandoc/Readers/Docx.hs | 2 +- src/Text/Pandoc/Readers/Docx/Parse.hs | 4 ++-- src/Text/Pandoc/Readers/Markdown.hs | 2 +- src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs | 8 ++++---- src/Text/Pandoc/Writers/Docx.hs | 6 +++--- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- src/Text/Pandoc/Writers/EPUB.hs | 4 ++-- src/Text/Pandoc/Writers/Haddock.hs | 4 ++-- src/Text/Pandoc/Writers/Muse.hs | 4 ++-- src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 20 ++++++++++---------- src/Text/Pandoc/Writers/Shared.hs | 2 +- test/Tests/Old.hs | 1 - test/Tests/Readers/Muse.hs | 2 +- test/Tests/Readers/RST.hs | 2 +- test/Tests/Readers/Txt2Tags.hs | 2 +- test/Tests/Writers/RST.hs | 2 +- 18 files changed, 40 insertions(+), 41 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 4c76aac13..e7698d148 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -126,7 +126,7 @@ imageType img = case B.take 4 img of | B.take 4 (B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF" -> return Eps "\x01\x00\x00\x00" - | B.take 4 (B.drop 40 img) == " EMF" + | B.take 4 (B.drop 40 img) == " EMF" -> return Emf _ -> mzero @@ -361,9 +361,9 @@ svgSize opts img = do , dpiX = dpi , dpiY = dpi } - + emfSize :: ByteString -> Maybe ImageSize -emfSize img = +emfSize img = let parseheader = runGetOrFail $ do skip 0x18 -- 0x00 @@ -388,11 +388,11 @@ emfSize img = , dpiX = fromIntegral dpiW , dpiY = fromIntegral dpiH } - in + in case parseheader . BL.fromStrict $ img of Left _ -> Nothing Right (_, _, size) -> Just size - + jpegSize :: ByteString -> Either String ImageSize jpegSize img = diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index b7149af39..c1c40c299 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -132,7 +132,7 @@ class PushViaCall a where instance PushViaCall (Lua ()) where pushViaCall' fn pushArgs num = do Lua.push fn - Lua.rawget (Lua.registryindex) + Lua.rawget Lua.registryindex pushArgs call num 1 diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 104e17c18..9b41e468a 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -367,7 +367,7 @@ blocksToInlinesWarn cmtId blks = do parPartToInlines :: PandocMonad m => ParPart -> DocxContext m Inlines parPartToInlines parPart = case parPart of - (BookMark _ anchor) | notElem anchor dummyAnchors -> do + (BookMark _ anchor) | anchor `notElem` dummyAnchors -> do inHdrBool <- asks docxInHeaderBlock ils <- parPartToInlines' parPart immedPrevAnchor <- gets docxImmedPrevAnchor diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index dcf2e0493..d6226dfab 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -136,9 +136,9 @@ unwrap :: NameSpaces -> Content -> [Content] unwrap ns (Elem element) | isElem ns "w" "sdt" element , Just sdtContent <- findChildByName ns "w" "sdtContent" element - = concatMap (unwrap ns) $ map Elem $ elChildren sdtContent + = concatMap ((unwrap ns) . Elem) (elChildren sdtContent) | isElem ns "w" "smartTag" element - = concatMap (unwrap ns) $ map Elem $ elChildren element + = concatMap ((unwrap ns) . Elem) (elChildren element) unwrap _ content = [content] unwrapChild :: NameSpaces -> Content -> Content diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 237f1aa0c..f6efef657 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -161,7 +161,7 @@ inlinesInBalancedBrackets = stripBracket xs = if last xs == ']' then init xs else xs go :: PandocMonad m => Int -> MarkdownParser m () go 0 = return () - go openBrackets = + go openBrackets = (() <$ (escapedChar <|> code <|> rawHtmlInline <|> diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs index ef8b2d18a..e9ce53704 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs @@ -61,13 +61,13 @@ and6 :: (Arrow a) => a b c0->a b c1->a b c2->a b c3->a b c4->a b c5 -> a b (c0,c1,c2,c3,c4,c5 ) -and3 a b c = (and2 a b ) &&& c +and3 a b c = and2 a b &&& c >>^ \((z,y ) , x) -> (z,y,x ) -and4 a b c d = (and3 a b c ) &&& d +and4 a b c d = and3 a b c &&& d >>^ \((z,y,x ) , w) -> (z,y,x,w ) -and5 a b c d e = (and4 a b c d ) &&& e +and5 a b c d e = and4 a b c d &&& e >>^ \((z,y,x,w ) , v) -> (z,y,x,w,v ) -and6 a b c d e f = (and5 a b c d e ) &&& f +and6 a b c d e f = and5 a b c d e &&& f >>^ \((z,y,x,w,v ) , u) -> (z,y,x,w,v,u ) liftA2 :: (Arrow a) => (x -> y -> z) -> a b x -> a b y -> a b z diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 2c03b3450..6422f61bf 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1337,7 +1337,7 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do imgElt case stImage of - Just imgData -> return $ [generateImgElt imgData] + Just imgData -> return [generateImgElt imgData] Nothing -> ( do --try (img, mt) <- P.fetchItem src ident <- ("rId"++) `fmap` getUniqueId @@ -1386,12 +1386,12 @@ breakElement kind = mknode "w:r" [] [mknode "w:br" [("w:type",kind)] () ] defaultFootnotes :: [Element] defaultFootnotes = [ mknode "w:footnote" [("w:type", "separator"), ("w:id", "-1")] - [ mknode "w:p" [] $ + [ mknode "w:p" [] [mknode "w:r" [] $ [ mknode "w:separator" [] ()]]] , mknode "w:footnote" [("w:type", "continuationSeparator"), ("w:id", "0")] - [ mknode "w:p" [] $ + [ mknode "w:p" [] [ mknode "w:r" [] $ [ mknode "w:continuationSeparator" [] ()]]]] diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 523830e28..a74c23764 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -372,9 +372,9 @@ backSlashLineBreaks :: [String] -> String backSlashLineBreaks ls = vcatBackSlash $ map escape ls where vcatBackSlash = intercalate "\\\\ \\\\ " -- simulate paragraphs. - escape ('\n':[]) = "" -- remove trailing newlines + escape ['\n'] = "" -- remove trailing newlines escape ('\n':cs) = "\\\\ " ++ escape cs - escape (c:cs) = c : (escape cs) + escape (c:cs) = c : escape cs escape [] = [] -- Auxiliary functions for tables: diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 7b4853a24..cf50e9bb9 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -458,7 +458,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do -- mediaRef <- P.newIORef [] Pandoc _ blocks <- walkM (transformInline opts') doc >>= walkM transformBlock - picEntries <- (mapMaybe (snd . snd)) <$> gets stMediaPaths + picEntries <- mapMaybe (snd . snd) <$> gets stMediaPaths -- handle fonts let matchingGlob f = do xs <- lift $ P.glob f @@ -872,7 +872,7 @@ metadataElement version md currentTime = dcTag' n s = [dcTag n s] toIdentifierNode id' (Identifier txt scheme) | version == EPUB2 = [dcNode "identifier" ! - ([("id",id')] ++ maybe [] (\x -> [("opf:scheme", x)]) scheme) $ + (("id",id') : maybe [] (\x -> [("opf:scheme", x)]) scheme) $ txt] | otherwise = [dcNode "identifier" ! [("id",id')] $ txt] ++ maybe [] (\x -> [unode "meta" ! diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 3f96f5802..dfa1d8b57 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TupleSections #-} + {- Copyright (C) 2014-2015, 2017-2018 John MacFarlane @@ -141,7 +141,7 @@ blockToHaddock opts (Table caption aligns widths headers rows) = do then empty else blankline <> caption' <> blankline tbl <- gridTable opts blockListToHaddock - (all null headers) (map (\_ -> AlignDefault) aligns) + (all null headers) (map (const AlignDefault) aligns) widths headers rows return $ prefixed "> " (tbl $$ blankline $$ caption'') $$ blankline blockToHaddock opts (BulletList items) = do diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 8a8217d94..5dda951c5 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -373,7 +373,7 @@ inlineToMuse (Superscript lst) = do inlineToMuse (Subscript lst) = do contents <- inlineListToMuse lst return $ "" <> contents <> "" -inlineToMuse (SmallCaps {}) = +inlineToMuse SmallCaps {} = fail "SmallCaps should be expanded before normalization" inlineToMuse (Quoted SingleQuote lst) = do contents <- inlineListToMuse lst @@ -381,7 +381,7 @@ inlineToMuse (Quoted SingleQuote lst) = do inlineToMuse (Quoted DoubleQuote lst) = do contents <- inlineListToMuse lst return $ "“" <> contents <> "”" -inlineToMuse (Cite {}) = +inlineToMuse Cite {} = fail "Citations should be expanded before normalization" inlineToMuse (Code _ str) = return $ "" <> text (substitute "" "</code>" str) <> "" diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 396469edd..fcd124e76 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -474,7 +474,7 @@ blockToParagraphs (DefinitionList entries) = do definition <- concatMapM (blockToParagraphs . BlockQuote) blksLst return $ term ++ definition concatMapM go entries -blockToParagraphs (Div (_, "notes" : [], _) blks) = +blockToParagraphs (Div (_, ["notes"], _) blks) = local (\env -> env{envInSpeakerNotes=True}) $ do sldId <- asks envCurSlideId spkNotesMap <- gets stSpeakerNotesMap @@ -558,7 +558,7 @@ blockToShape blk = do paras <- blockToParagraphs blk combineShapes :: [Shape] -> [Shape] combineShapes [] = [] combineShapes[s] = [s] -combineShapes (pic@(Pic{}) : ss) = pic : combineShapes ss +combineShapes (pic@Pic{} : ss) = pic : combineShapes ss combineShapes (TextBox [] : ss) = combineShapes ss combineShapes (s : TextBox [] : ss) = combineShapes (s : ss) combineShapes (TextBox (p:ps) : TextBox (p':ps') : ss) = @@ -569,8 +569,8 @@ blocksToShapes :: [Block] -> Pres [Shape] blocksToShapes blks = combineShapes <$> mapM blockToShape blks isImage :: Inline -> Bool -isImage (Image{}) = True -isImage (Link _ (Image _ _ _ : _) _) = True +isImage Image{} = True +isImage (Link _ (Image{} : _) _) = True isImage _ = False splitBlocks' :: [Block] -> [[Block]] -> [Block] -> Pres [[Block]] @@ -589,23 +589,23 @@ splitBlocks' cur acc (Plain ils : blks) = splitBlocks' cur acc (Para ils : blks) splitBlocks' cur acc (Para (il:ils) : blks) | isImage il = do slideLevel <- asks envSlideLevel case cur of - [(Header n _ _)] | n == slideLevel -> + [Header n _ _] | n == slideLevel -> splitBlocks' [] (acc ++ [cur ++ [Para [il]]]) (if null ils then blks else Para ils : blks) _ -> splitBlocks' [] (acc ++ (if null cur then [] else [cur]) ++ [[Para [il]]]) (if null ils then blks else Para ils : blks) -splitBlocks' cur acc (tbl@(Table{}) : blks) = do +splitBlocks' cur acc (tbl@Table{} : blks) = do slideLevel <- asks envSlideLevel case cur of - [(Header n _ _)] | n == slideLevel -> + [Header n _ _] | n == slideLevel -> splitBlocks' [] (acc ++ [cur ++ [tbl]]) blks _ -> splitBlocks' [] (acc ++ (if null cur then [] else [cur]) ++ [[tbl]]) blks splitBlocks' cur acc (d@(Div (_, classes, _) _): blks) | "columns" `elem` classes = do slideLevel <- asks envSlideLevel case cur of - [(Header n _ _)] | n == slideLevel -> + [Header n _ _] | n == slideLevel -> splitBlocks' [] (acc ++ [cur ++ [d]]) blks _ -> splitBlocks' [] (acc ++ (if null cur then [] else [cur]) ++ [[d]]) blks splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks @@ -617,7 +617,7 @@ getSpeakerNotes :: Pres (Maybe SpeakerNotes) getSpeakerNotes = do sldId <- asks envCurSlideId spkNtsMap <- gets stSpeakerNotesMap - return $ (SpeakerNotes . concat . reverse) <$> (M.lookup sldId spkNtsMap) + return $ (SpeakerNotes . concat . reverse) <$> M.lookup sldId spkNtsMap blocksToSlide' :: Int -> [Block] -> Pres Slide blocksToSlide' lvl (Header n (ident, _, _) ils : blks) @@ -864,7 +864,7 @@ emptyParagraph para = all emptyParaElem $ paraElems para emptyShape :: Shape -> Bool -emptyShape (TextBox paras) = all emptyParagraph $ paras +emptyShape (TextBox paras) = all emptyParagraph paras emptyShape _ = False emptyLayout :: Layout -> Bool diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index a0482fdbf..964db5ecc 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -289,7 +289,7 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do -- on command line options, widths given in this specific table, and -- cells' contents let handleWidths - | (writerWrapText opts) == WrapNone = handleFullWidths + | writerWrapText opts == WrapNone = handleFullWidths | all (== 0) widths = handleZeroWidths | otherwise = handleGivenWidths widths (widthsInChars, rawHeaders, rawRows) <- handleWidths diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index b82251a56..ed4dcc076 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -286,4 +286,3 @@ findDynlibDir :: [FilePath] -> Maybe FilePath findDynlibDir [] = Nothing findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) "build" findDynlibDir (_:xs) = findDynlibDir xs - diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 7cb220f03..89dbbc345 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -175,7 +175,7 @@ tests = , "Class tag without name" =: "foobar" =?> para (spanWith ("", [], []) "foobar") -- tag should match with the last tag, not verbatim one - , "Nested \"\" inside em tag" =: "foobar" =?> para (emph ("foobar")) + , "Nested \"\" inside em tag" =: "foobar" =?> para (emph "foobar") , testGroup "Links" [ "Link without description" =: diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs index 3753fbf12..305c7060b 100644 --- a/test/Tests/Readers/RST.hs +++ b/test/Tests/Readers/RST.hs @@ -184,6 +184,6 @@ tests = [ "line block with blank line" =: , ".. [1]" , " bar" ] =?> - para ("foo" <> (note $ para "bar")) + para ("foo" <> note (para "bar")) ] ] diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index 435d983a1..e3646e95e 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -143,7 +143,7 @@ tests = , "Header with label" =: "= header =[label]" =?> - headerWith ("label", [], []) 1 ("header") + headerWith ("label", [], []) 1 "header" , "Invalid header, mismatched delimiters" =: "== header =" =?> diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 884281af2..e54ce4737 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -61,7 +61,7 @@ tests = [ testGroup "rubrics" -- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup strong (space <> str "text" <> space <> space) =?> "**text**" , "single space stripped" =: - strong (space) =?> "" + strong space =?> "" ] , testGroup "headings" [ "normal heading" =: -- cgit v1.2.3 From 7e389cb3dbdc11126b9bdb6a7741a65e5a94a43e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 18 Mar 2018 10:46:28 -0700 Subject: Use NoImplicitPrelude and explicitly import Prelude. This seems to be necessary if we are to use our custom Prelude with ghci. Closes #4464. --- pandoc.hs | 2 ++ src/Text/Pandoc/App.hs | 2 ++ src/Text/Pandoc/Asciify.hs | 2 ++ src/Text/Pandoc/BCP47.hs | 2 ++ src/Text/Pandoc/CSS.hs | 2 ++ src/Text/Pandoc/CSV.hs | 2 ++ src/Text/Pandoc/Class.hs | 2 ++ src/Text/Pandoc/Data.hs | 2 ++ src/Text/Pandoc/Emoji.hs | 2 ++ src/Text/Pandoc/Error.hs | 2 ++ src/Text/Pandoc/Extensions.hs | 2 ++ src/Text/Pandoc/Filter.hs | 2 ++ src/Text/Pandoc/Filter/JSON.hs | 2 ++ src/Text/Pandoc/Filter/Lua.hs | 2 ++ src/Text/Pandoc/Filter/Path.hs | 2 ++ src/Text/Pandoc/Highlighting.hs | 2 ++ src/Text/Pandoc/ImageSize.hs | 2 ++ src/Text/Pandoc/Logging.hs | 2 ++ src/Text/Pandoc/Lua.hs | 2 ++ src/Text/Pandoc/Lua/Filter.hs | 2 ++ src/Text/Pandoc/Lua/Init.hs | 2 ++ src/Text/Pandoc/Lua/Module/MediaBag.hs | 2 ++ src/Text/Pandoc/Lua/Module/Pandoc.hs | 2 ++ src/Text/Pandoc/Lua/Module/Utils.hs | 2 ++ src/Text/Pandoc/Lua/Packages.hs | 2 ++ src/Text/Pandoc/Lua/StackInstances.hs | 2 ++ src/Text/Pandoc/Lua/Util.hs | 2 ++ src/Text/Pandoc/MIME.hs | 2 ++ src/Text/Pandoc/MediaBag.hs | 2 ++ src/Text/Pandoc/Options.hs | 2 ++ src/Text/Pandoc/PDF.hs | 2 ++ src/Text/Pandoc/Parsing.hs | 2 ++ src/Text/Pandoc/Pretty.hs | 2 ++ src/Text/Pandoc/Process.hs | 2 ++ src/Text/Pandoc/Readers.hs | 2 ++ src/Text/Pandoc/Readers/CommonMark.hs | 2 ++ src/Text/Pandoc/Readers/Creole.hs | 2 ++ src/Text/Pandoc/Readers/DocBook.hs | 2 ++ src/Text/Pandoc/Readers/Docx.hs | 2 ++ src/Text/Pandoc/Readers/Docx/Combine.hs | 2 ++ src/Text/Pandoc/Readers/Docx/Fields.hs | 2 ++ src/Text/Pandoc/Readers/Docx/Lists.hs | 2 ++ src/Text/Pandoc/Readers/Docx/Parse.hs | 2 ++ src/Text/Pandoc/Readers/Docx/StyleMap.hs | 2 ++ src/Text/Pandoc/Readers/Docx/Util.hs | 2 ++ src/Text/Pandoc/Readers/EPUB.hs | 2 ++ src/Text/Pandoc/Readers/HTML.hs | 2 ++ src/Text/Pandoc/Readers/Haddock.hs | 2 ++ src/Text/Pandoc/Readers/JATS.hs | 2 ++ src/Text/Pandoc/Readers/LaTeX.hs | 2 ++ src/Text/Pandoc/Readers/LaTeX/Types.hs | 2 ++ src/Text/Pandoc/Readers/Markdown.hs | 2 ++ src/Text/Pandoc/Readers/MediaWiki.hs | 2 ++ src/Text/Pandoc/Readers/Muse.hs | 2 ++ src/Text/Pandoc/Readers/Native.hs | 2 ++ src/Text/Pandoc/Readers/OPML.hs | 2 ++ src/Text/Pandoc/Readers/Odt.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Arrows/State.hs | 4 ++-- src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Base.hs | 2 -- src/Text/Pandoc/Readers/Odt/ContentReader.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Generic/Utils.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs | 2 ++ src/Text/Pandoc/Readers/Odt/Namespaces.hs | 2 ++ src/Text/Pandoc/Readers/Odt/StyleReader.hs | 2 ++ src/Text/Pandoc/Readers/Org.hs | 2 ++ src/Text/Pandoc/Readers/Org/BlockStarts.hs | 2 ++ src/Text/Pandoc/Readers/Org/Blocks.hs | 2 ++ src/Text/Pandoc/Readers/Org/DocumentTree.hs | 2 ++ src/Text/Pandoc/Readers/Org/ExportSettings.hs | 2 ++ src/Text/Pandoc/Readers/Org/Inlines.hs | 2 ++ src/Text/Pandoc/Readers/Org/Meta.hs | 2 ++ src/Text/Pandoc/Readers/Org/ParserState.hs | 2 ++ src/Text/Pandoc/Readers/Org/Parsing.hs | 2 ++ src/Text/Pandoc/Readers/Org/Shared.hs | 2 ++ src/Text/Pandoc/Readers/RST.hs | 2 ++ src/Text/Pandoc/Readers/TWiki.hs | 2 ++ src/Text/Pandoc/Readers/Textile.hs | 2 ++ src/Text/Pandoc/Readers/TikiWiki.hs | 2 ++ src/Text/Pandoc/Readers/Txt2Tags.hs | 2 ++ src/Text/Pandoc/Readers/Vimwiki.hs | 2 ++ src/Text/Pandoc/SelfContained.hs | 2 ++ src/Text/Pandoc/Shared.hs | 2 ++ src/Text/Pandoc/Slides.hs | 2 ++ src/Text/Pandoc/Templates.hs | 2 ++ src/Text/Pandoc/Translations.hs | 2 ++ src/Text/Pandoc/UTF8.hs | 1 + src/Text/Pandoc/UUID.hs | 2 ++ src/Text/Pandoc/Writers.hs | 2 ++ src/Text/Pandoc/Writers/AsciiDoc.hs | 2 ++ src/Text/Pandoc/Writers/CommonMark.hs | 2 ++ src/Text/Pandoc/Writers/ConTeXt.hs | 2 ++ src/Text/Pandoc/Writers/Custom.hs | 2 ++ src/Text/Pandoc/Writers/Docbook.hs | 2 ++ src/Text/Pandoc/Writers/Docx.hs | 2 ++ src/Text/Pandoc/Writers/DokuWiki.hs | 2 ++ src/Text/Pandoc/Writers/EPUB.hs | 2 ++ src/Text/Pandoc/Writers/FB2.hs | 2 ++ src/Text/Pandoc/Writers/HTML.hs | 2 ++ src/Text/Pandoc/Writers/Haddock.hs | 2 ++ src/Text/Pandoc/Writers/ICML.hs | 2 ++ src/Text/Pandoc/Writers/JATS.hs | 2 ++ src/Text/Pandoc/Writers/LaTeX.hs | 2 ++ src/Text/Pandoc/Writers/Man.hs | 2 ++ src/Text/Pandoc/Writers/Markdown.hs | 2 ++ src/Text/Pandoc/Writers/Math.hs | 2 ++ src/Text/Pandoc/Writers/MediaWiki.hs | 2 ++ src/Text/Pandoc/Writers/Ms.hs | 2 ++ src/Text/Pandoc/Writers/Muse.hs | 6 ++++-- src/Text/Pandoc/Writers/Native.hs | 2 ++ src/Text/Pandoc/Writers/ODT.hs | 2 ++ src/Text/Pandoc/Writers/OOXML.hs | 2 ++ src/Text/Pandoc/Writers/OPML.hs | 2 ++ src/Text/Pandoc/Writers/OpenDocument.hs | 2 ++ src/Text/Pandoc/Writers/Org.hs | 2 ++ src/Text/Pandoc/Writers/Powerpoint.hs | 2 ++ src/Text/Pandoc/Writers/Powerpoint/Output.hs | 2 ++ src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 2 ++ src/Text/Pandoc/Writers/RST.hs | 2 ++ src/Text/Pandoc/Writers/RTF.hs | 2 ++ src/Text/Pandoc/Writers/Shared.hs | 2 ++ src/Text/Pandoc/Writers/TEI.hs | 2 ++ src/Text/Pandoc/Writers/Texinfo.hs | 2 ++ src/Text/Pandoc/Writers/Textile.hs | 2 ++ src/Text/Pandoc/Writers/ZimWiki.hs | 2 ++ src/Text/Pandoc/XML.hs | 2 ++ stack.yaml | 7 ++----- test/Tests/Command.hs | 2 ++ test/Tests/Helpers.hs | 2 ++ test/Tests/Lua.hs | 2 ++ test/Tests/Old.hs | 2 ++ test/Tests/Readers/Creole.hs | 2 ++ test/Tests/Readers/Docx.hs | 2 ++ test/Tests/Readers/EPUB.hs | 2 ++ test/Tests/Readers/HTML.hs | 2 ++ test/Tests/Readers/JATS.hs | 2 ++ test/Tests/Readers/LaTeX.hs | 2 ++ test/Tests/Readers/Markdown.hs | 2 ++ test/Tests/Readers/Muse.hs | 2 ++ test/Tests/Readers/Odt.hs | 2 ++ test/Tests/Readers/Org/Block.hs | 2 ++ test/Tests/Readers/Org/Block/CodeBlock.hs | 2 ++ test/Tests/Readers/Org/Block/Figure.hs | 2 ++ test/Tests/Readers/Org/Block/Header.hs | 2 ++ test/Tests/Readers/Org/Block/List.hs | 2 ++ test/Tests/Readers/Org/Block/Table.hs | 2 ++ test/Tests/Readers/Org/Directive.hs | 2 ++ test/Tests/Readers/Org/Inline.hs | 2 ++ test/Tests/Readers/Org/Inline/Citation.hs | 2 ++ test/Tests/Readers/Org/Inline/Note.hs | 2 ++ test/Tests/Readers/Org/Inline/Smart.hs | 2 ++ test/Tests/Readers/Org/Meta.hs | 2 ++ test/Tests/Readers/Org/Shared.hs | 2 ++ test/Tests/Readers/RST.hs | 2 ++ test/Tests/Readers/Txt2Tags.hs | 2 ++ test/Tests/Shared.hs | 2 ++ test/Tests/Writers/AsciiDoc.hs | 2 ++ test/Tests/Writers/ConTeXt.hs | 2 ++ test/Tests/Writers/Docbook.hs | 2 ++ test/Tests/Writers/Docx.hs | 2 ++ test/Tests/Writers/FB2.hs | 2 ++ test/Tests/Writers/HTML.hs | 2 ++ test/Tests/Writers/JATS.hs | 2 ++ test/Tests/Writers/LaTeX.hs | 2 ++ test/Tests/Writers/Markdown.hs | 2 ++ test/Tests/Writers/Muse.hs | 2 ++ test/Tests/Writers/Native.hs | 2 ++ test/Tests/Writers/OOXML.hs | 2 ++ test/Tests/Writers/Org.hs | 2 ++ test/Tests/Writers/Plain.hs | 2 ++ test/Tests/Writers/Powerpoint.hs | 2 ++ test/Tests/Writers/RST.hs | 2 ++ test/Tests/Writers/TEI.hs | 2 ++ test/test-pandoc.hs | 2 ++ 177 files changed, 353 insertions(+), 11 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/pandoc.hs b/pandoc.hs index 780e41ce1..7e7749aa5 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -29,6 +30,7 @@ Parses command-line options and calls the appropriate readers and writers. -} module Main where +import Prelude import qualified Control.Exception as E import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions) import Text.Pandoc.Error (handleError) diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 992cecb83..76d1d79c0 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -42,6 +43,7 @@ module Text.Pandoc.App ( , options , applyFilters ) where +import Prelude import qualified Control.Exception as E import Control.Monad import Control.Monad.Except (catchError, throwError) diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs index 11d3eddac..2de670270 100644 --- a/src/Text/Pandoc/Asciify.hs +++ b/src/Text/Pandoc/Asciify.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2013-2018 John MacFarlane @@ -30,6 +31,7 @@ ascii equivalents (used in constructing HTML identifiers). -} module Text.Pandoc.Asciify (toAsciiChar) where +import Prelude import Data.Char (isAscii) import qualified Data.Map as M diff --git a/src/Text/Pandoc/BCP47.hs b/src/Text/Pandoc/BCP47.hs index 2dd825142..7aadea52a 100644 --- a/src/Text/Pandoc/BCP47.hs +++ b/src/Text/Pandoc/BCP47.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2017–2018 John MacFarlane @@ -34,6 +35,7 @@ module Text.Pandoc.BCP47 ( , renderLang ) where +import Prelude import Control.Monad (guard) import Data.Char (isAlphaNum, isAscii, isLetter, isLower, isUpper, toLower, toUpper) diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs index d44b5e1e2..2141b8430 100644 --- a/src/Text/Pandoc/CSS.hs +++ b/src/Text/Pandoc/CSS.hs @@ -1,9 +1,11 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Text.Pandoc.CSS ( foldOrElse , pickStyleAttrProps , pickStylesToKVs ) where +import Prelude import Text.Pandoc.Shared (trim) import Text.Parsec import Text.Parsec.String diff --git a/src/Text/Pandoc/CSV.hs b/src/Text/Pandoc/CSV.hs index 3415ae88f..96bfd6d89 100644 --- a/src/Text/Pandoc/CSV.hs +++ b/src/Text/Pandoc/CSV.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2017–2018 John MacFarlane @@ -34,6 +35,7 @@ module Text.Pandoc.CSV ( ParseError ) where +import Prelude import Control.Monad (void) import Data.Text (Text) import qualified Data.Text as T diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 40927252f..62341ba16 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE DeriveFunctor #-} @@ -96,6 +97,7 @@ module Text.Pandoc.Class ( PandocMonad(..) , Translations ) where +import Prelude import Prelude hiding (readFile) import System.Random (StdGen, next, mkStdGen) import qualified System.Random as IO (newStdGen) diff --git a/src/Text/Pandoc/Data.hs b/src/Text/Pandoc/Data.hs index af0e4504f..2cf0d3f81 100644 --- a/src/Text/Pandoc/Data.hs +++ b/src/Text/Pandoc/Data.hs @@ -1,7 +1,9 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Text.Pandoc.Data (dataFiles) where +import Prelude import qualified Data.ByteString as B import Data.FileEmbed import System.FilePath (splitDirectories) diff --git a/src/Text/Pandoc/Emoji.hs b/src/Text/Pandoc/Emoji.hs index 3766960ea..5cc965153 100644 --- a/src/Text/Pandoc/Emoji.hs +++ b/src/Text/Pandoc/Emoji.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015 John MacFarlane @@ -28,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Emoji symbol lookup from canonical string identifier. -} module Text.Pandoc.Emoji ( emojis ) where +import Prelude import qualified Data.Map as M emojis :: M.Map String String diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index f78a31481..feb047f68 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {- @@ -34,6 +35,7 @@ module Text.Pandoc.Error ( PandocError(..), handleError) where +import Prelude import Control.Exception (Exception) import Data.Typeable (Typeable) import GHC.Generics (Generic) diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index f1a264d82..631042088 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} @@ -48,6 +49,7 @@ module Text.Pandoc.Extensions ( Extension(..) , githubMarkdownExtensions , multimarkdownExtensions ) where +import Prelude import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions) import Data.Aeson.TH (deriveJSON) import Data.Bits (clearBit, setBit, testBit, (.|.)) diff --git a/src/Text/Pandoc/Filter.hs b/src/Text/Pandoc/Filter.hs index e2a3c3e16..5461648e1 100644 --- a/src/Text/Pandoc/Filter.hs +++ b/src/Text/Pandoc/Filter.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2017 John MacFarlane @@ -33,6 +34,7 @@ module Text.Pandoc.Filter , applyFilters ) where +import Prelude import Data.Aeson (defaultOptions) import Data.Aeson.TH (deriveJSON) import Data.Foldable (foldrM) diff --git a/src/Text/Pandoc/Filter/JSON.hs b/src/Text/Pandoc/Filter/JSON.hs index 5772c2c41..97b291603 100644 --- a/src/Text/Pandoc/Filter/JSON.hs +++ b/src/Text/Pandoc/Filter/JSON.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -29,6 +30,7 @@ Programmatically modifications of pandoc documents via JSON filters. -} module Text.Pandoc.Filter.JSON (apply) where +import Prelude import Control.Monad (unless, when) import Control.Monad.Trans (MonadIO (liftIO)) import Data.Aeson (eitherDecode', encode) diff --git a/src/Text/Pandoc/Filter/Lua.hs b/src/Text/Pandoc/Filter/Lua.hs index 597a31cbc..d559fb912 100644 --- a/src/Text/Pandoc/Filter/Lua.hs +++ b/src/Text/Pandoc/Filter/Lua.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -29,6 +30,7 @@ Apply Lua filters to modify a pandoc documents programmatically. -} module Text.Pandoc.Filter.Lua (apply) where +import Prelude import Control.Exception (throw) import Text.Pandoc.Class (PandocIO) import Text.Pandoc.Definition (Pandoc) diff --git a/src/Text/Pandoc/Filter/Path.hs b/src/Text/Pandoc/Filter/Path.hs index 8074bcbb7..f244597aa 100644 --- a/src/Text/Pandoc/Filter/Path.hs +++ b/src/Text/Pandoc/Filter/Path.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -31,6 +32,7 @@ module Text.Pandoc.Filter.Path ( expandFilterPath ) where +import Prelude import Text.Pandoc.Class (PandocMonad, fileExists, getUserDataDir) import System.FilePath ((), isRelative) diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index 113727750..70bb70302 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2008-2018 John MacFarlane @@ -49,6 +50,7 @@ module Text.Pandoc.Highlighting ( highlightingStyles , fromListingsLanguage , toListingsLanguage ) where +import Prelude import Control.Monad import Data.Char (toLower) import qualified Data.Map as M diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index e7698d148..c5fe98a66 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} {- @@ -49,6 +50,7 @@ module Text.Pandoc.ImageSize ( ImageType(..) , showInPixel , showFl ) where +import Prelude import Data.ByteString (ByteString, unpack) import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy as BL diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index b22c08467..07ed2e570 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} @@ -39,6 +40,7 @@ module Text.Pandoc.Logging ( , messageVerbosity ) where +import Prelude import Control.Monad (mzero) import Data.Aeson import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs index 79955509d..cd7117074 100644 --- a/src/Text/Pandoc/Lua.hs +++ b/src/Text/Pandoc/Lua.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017–2018 Albert Krewinkel @@ -31,6 +32,7 @@ module Text.Pandoc.Lua , runPandocLua ) where +import Prelude import Control.Monad ((>=>)) import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..), Status (OK), ToLuaStack (push)) diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs index cc2b9d47e..264066305 100644 --- a/src/Text/Pandoc/Lua/Filter.hs +++ b/src/Text/Pandoc/Lua/Filter.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} module Text.Pandoc.Lua.Filter ( LuaFilterFunction @@ -10,6 +11,7 @@ module Text.Pandoc.Lua.Filter ( LuaFilterFunction , blockElementNames , inlineElementNames ) where +import Prelude import Control.Monad (mplus, unless, when, (>=>)) import Control.Monad.Catch (finally) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs index 8fa228837..c8c7fdfbd 100644 --- a/src/Text/Pandoc/Lua/Init.hs +++ b/src/Text/Pandoc/Lua/Init.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017-2018 Albert Krewinkel @@ -34,6 +35,7 @@ module Text.Pandoc.Lua.Init , registerScriptPath ) where +import Prelude import Control.Monad.Trans (MonadIO (..)) import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr) import Data.IORef (newIORef, readIORef) diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs index 7d942a452..f48fe56c5 100644 --- a/src/Text/Pandoc/Lua/Module/MediaBag.hs +++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017-2018 Albert Krewinkel @@ -29,6 +30,7 @@ module Text.Pandoc.Lua.Module.MediaBag ( pushModule ) where +import Prelude import Control.Monad (zipWithM_) import Data.IORef (IORef, modifyIORef', readIORef) import Data.Maybe (fromMaybe) diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs index b9410a353..8cb630d7b 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017-2018 Albert Krewinkel @@ -30,6 +31,7 @@ module Text.Pandoc.Lua.Module.Pandoc ( pushModule ) where +import Prelude import Control.Monad (when) import Data.Default (Default (..)) import Data.Maybe (fromMaybe) diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index f8eb96dc7..7fa4616be 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017-2018 Albert Krewinkel @@ -29,6 +30,7 @@ module Text.Pandoc.Lua.Module.Utils ( pushModule ) where +import Prelude import Control.Applicative ((<|>)) import Data.Default (def) import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults) diff --git a/src/Text/Pandoc/Lua/Packages.hs b/src/Text/Pandoc/Lua/Packages.hs index 1e6ff22fe..59637826e 100644 --- a/src/Text/Pandoc/Lua/Packages.hs +++ b/src/Text/Pandoc/Lua/Packages.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017-2018 Albert Krewinkel @@ -32,6 +33,7 @@ module Text.Pandoc.Lua.Packages , installPandocPackageSearcher ) where +import Prelude import Control.Monad (forM_) import Data.ByteString.Char8 (unpack) import Data.IORef (IORef) diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index 7e0dc20c4..3298079c5 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2012-2018 John MacFarlane 2017-2018 Albert Krewinkel @@ -33,6 +34,7 @@ StackValue instances for pandoc types. -} module Text.Pandoc.Lua.StackInstances () where +import Prelude import Control.Applicative ((<|>)) import Control.Monad (when) import Control.Monad.Catch (finally) diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index c1c40c299..ea9ec2554 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2012-2018 John MacFarlane 2017-2018 Albert Krewinkel @@ -46,6 +47,7 @@ module Text.Pandoc.Lua.Util , dostring' ) where +import Prelude import Control.Monad (when) import Control.Monad.Catch (finally) import Data.ByteString.Char8 (unpack) diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 43abe9b2f..2f37c1b83 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2011-2018 John MacFarlane @@ -29,6 +30,7 @@ Mime type lookup for ODT writer. -} module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef, extensionFromMimeType )where +import Prelude import Data.Char (toLower) import Data.List (isPrefixOf, isSuffixOf) import qualified Data.Map as M diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs index 6f4cb8fee..bb0d60aff 100644 --- a/src/Text/Pandoc/MediaBag.hs +++ b/src/Text/Pandoc/MediaBag.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} @@ -37,6 +38,7 @@ module Text.Pandoc.MediaBag ( insertMedia, mediaDirectory, ) where +import Prelude import qualified Data.ByteString.Lazy as BL import Data.Data (Data) import qualified Data.Map as M diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index bd4ab252b..a542954ad 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TemplateHaskell #-} @@ -46,6 +47,7 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions , def , isEnabled ) where +import Prelude import Data.Aeson (defaultOptions) import Data.Aeson.TH (deriveJSON) import Data.Data (Data) diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 512786a78..06915cf6e 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -32,6 +33,7 @@ Conversion of LaTeX documents to PDF. -} module Text.Pandoc.PDF ( makePDF ) where +import Prelude import qualified Codec.Picture as JP import qualified Control.Exception as E import Control.Monad (unless, when) diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 64a380b1d..d488ea5cb 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE FlexibleContexts #-} @@ -195,6 +196,7 @@ module Text.Pandoc.Parsing ( takeWhileP, ) where +import Prelude import Control.Monad.Identity import Control.Monad.Reader import Data.Char (chr, isAlphaNum, isAscii, isAsciiUpper, isHexDigit, diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index ecfd340ef..de3d54ee2 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- @@ -77,6 +78,7 @@ module Text.Pandoc.Pretty ( ) where +import Prelude import Control.Monad import Control.Monad.State.Strict import Data.Char (isSpace) diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs index 27807a8c8..868977c86 100644 --- a/src/Text/Pandoc/Process.hs +++ b/src/Text/Pandoc/Process.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2013-2018 John MacFarlane @@ -29,6 +30,7 @@ ByteString variant of 'readProcessWithExitCode'. -} module Text.Pandoc.Process (pipeProcess) where +import Prelude import Control.Concurrent (forkIO, newEmptyMVar, putMVar, takeMVar) import Control.Exception import Control.Monad (unless) diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs index b9374ba06..4eff11c41 100644 --- a/src/Text/Pandoc/Readers.hs +++ b/src/Text/Pandoc/Readers.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -69,6 +70,7 @@ module Text.Pandoc.Readers , getDefaultExtensions ) where +import Prelude import Control.Monad.Except (throwError) import Data.Aeson import qualified Data.ByteString.Lazy as BL diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index 6fbc09c17..79a4abbc2 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015-2018 John MacFarlane @@ -32,6 +33,7 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org. module Text.Pandoc.Readers.CommonMark (readCommonMark) where +import Prelude import CMarkGFM import Control.Monad.State import Data.Char (isAlphaNum, isLetter, isSpace, toLower) diff --git a/src/Text/Pandoc/Readers/Creole.hs b/src/Text/Pandoc/Readers/Creole.hs index 5ca625229..4fd38c0fd 100644 --- a/src/Text/Pandoc/Readers/Creole.hs +++ b/src/Text/Pandoc/Readers/Creole.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2017 Sascha Wilde @@ -35,6 +36,7 @@ Conversion of creole text to 'Pandoc' document. module Text.Pandoc.Readers.Creole ( readCreole ) where +import Prelude import Control.Monad.Except (guard, liftM2, throwError) import qualified Data.Foldable as F import Data.Maybe (fromMaybe) diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 728f77a05..7789e3867 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ExplicitForAll #-} module Text.Pandoc.Readers.DocBook ( readDocBook ) where +import Prelude import Control.Monad.State.Strict import Data.Char (isSpace, toUpper) import Data.Default diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 9b41e468a..00603603a 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} @@ -74,6 +75,7 @@ module Text.Pandoc.Readers.Docx ( readDocx ) where +import Prelude import Codec.Archive.Zip import Control.Monad.Reader import Control.Monad.State.Strict diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs index 003265e6e..dfd2b5666 100644 --- a/src/Text/Pandoc/Readers/Docx/Combine.hs +++ b/src/Text/Pandoc/Readers/Docx/Combine.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE TypeSynonymInstances #-} @@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.Combine ( smushInlines ) where +import Prelude import Data.List import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr, (><), (|>)) import qualified Data.Sequence as Seq (null) diff --git a/src/Text/Pandoc/Readers/Docx/Fields.hs b/src/Text/Pandoc/Readers/Docx/Fields.hs index 6eeb55d2f..c3f54560b 100644 --- a/src/Text/Pandoc/Readers/Docx/Fields.hs +++ b/src/Text/Pandoc/Readers/Docx/Fields.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Jesse Rosenthal @@ -32,6 +33,7 @@ module Text.Pandoc.Readers.Docx.Fields ( FieldInfo(..) , parseFieldInfo ) where +import Prelude import Text.Parsec import Text.Parsec.String (Parser) diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs index c0f05094a..49ea71601 100644 --- a/src/Text/Pandoc/Readers/Docx/Lists.hs +++ b/src/Text/Pandoc/Readers/Docx/Lists.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Jesse Rosenthal @@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets , listParagraphDivs ) where +import Prelude import Data.List import Data.Maybe import Text.Pandoc.Generic (bottomUp) diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index d6226dfab..4c4c06073 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ViewPatterns #-} @@ -58,6 +59,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..) , archiveToDocx , archiveToDocxWithWarnings ) where +import Prelude import Codec.Archive.Zip import Control.Applicative ((<|>)) import Control.Monad.Except diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs index b32a73770..6ccda3ccc 100644 --- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs +++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..) , alterMap , getMap @@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..) , hasStyleName ) where +import Prelude import Control.Monad.State.Strict import Data.Char (toLower) import qualified Data.Map as M diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs index d9d65bc07..088950d26 100644 --- a/src/Text/Pandoc/Readers/Docx/Util.hs +++ b/src/Text/Pandoc/Readers/Docx/Util.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Text.Pandoc.Readers.Docx.Util ( NameSpaces , elemName @@ -8,6 +9,7 @@ module Text.Pandoc.Readers.Docx.Util ( , findAttrByName ) where +import Prelude import Data.Maybe (mapMaybe) import Text.XML.Light diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index fb17c1c8c..e77463fec 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TupleSections #-} @@ -7,6 +8,7 @@ module Text.Pandoc.Readers.EPUB (readEPUB) where +import Prelude import Codec.Archive.Zip (Archive (..), Entry, findEntryByPath, fromEntry, toArchiveOrFail) import Control.DeepSeq (NFData, deepseq) diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 13c87a9c7..b221b6fb2 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -42,6 +43,7 @@ module Text.Pandoc.Readers.HTML ( readHtml , isCommentTag ) where +import Prelude import Control.Applicative ((<|>)) import Control.Arrow (first) import Control.Monad (guard, mplus, msum, mzero, unless, void) diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 65fcc5dba..967037e4e 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {- | Module : Text.Pandoc.Readers.Haddock @@ -14,6 +15,7 @@ module Text.Pandoc.Readers.Haddock ( readHaddock ) where +import Prelude import Control.Monad.Except (throwError) import Data.List (intersperse, stripPrefix) import Data.Maybe (fromMaybe) diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index 8158a4511..b0a43ed06 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ExplicitForAll, TupleSections #-} module Text.Pandoc.Readers.JATS ( readJATS ) where +import Prelude import Control.Monad.State.Strict import Data.Char (isDigit, isSpace, toUpper) import Data.Default diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 7252a2da7..23b68361e 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} @@ -42,6 +43,7 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX, untokenize ) where +import Prelude import Control.Applicative (many, optional, (<|>)) import Control.Monad import Control.Monad.Except (throwError) diff --git a/src/Text/Pandoc/Readers/LaTeX/Types.hs b/src/Text/Pandoc/Readers/LaTeX/Types.hs index c9cbaa9b9..fa832114b 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Types.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Types.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2017-2018 John MacFarlane @@ -34,6 +35,7 @@ module Text.Pandoc.Readers.LaTeX.Types ( Tok(..) , SourcePos ) where +import Prelude import Data.Text (Text) import Text.Parsec.Pos (SourcePos) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index f6efef657..71e6f8249 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RelaxedPolyRec #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -32,6 +33,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document. -} module Text.Pandoc.Readers.Markdown ( readMarkdown ) where +import Prelude import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isAlphaNum, isPunctuation, isSpace, toLower) diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index d791a0a28..a07f66e7a 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE RelaxedPolyRec #-} {-# LANGUAGE TypeSynonymInstances #-} @@ -38,6 +39,7 @@ _ parse templates? -} module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where +import Prelude import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isDigit, isSpace) diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index bee4ae4d6..c9157b7d3 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {- Copyright (C) 2017-2018 Alexander Krotov @@ -39,6 +40,7 @@ TODO: -} module Text.Pandoc.Readers.Muse (readMuse) where +import Prelude import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isLetter) diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 88f6bfe8f..ef200aa19 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2011-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of a string representation of a pandoc type (@Pandoc@, -} module Text.Pandoc.Readers.Native ( readNative ) where +import Prelude import Text.Pandoc.Definition import Text.Pandoc.Options (ReaderOptions) import Text.Pandoc.Shared (safeRead) diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index 82266748f..57bdc96da 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} module Text.Pandoc.Readers.OPML ( readOPML ) where +import Prelude import Control.Monad.State.Strict import Data.Char (toUpper) import Data.Default diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs index 875c18a85..30016e444 100644 --- a/src/Text/Pandoc/Readers/Odt.hs +++ b/src/Text/Pandoc/Readers/Odt.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {- @@ -32,6 +33,7 @@ Entry point to the odt reader. module Text.Pandoc.Readers.Odt ( readOdt ) where +import Prelude import Codec.Archive.Zip import qualified Text.XML.Light as XML diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs index 202118669..971442613 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TupleSections #-} {- @@ -37,14 +38,13 @@ faster and easier to implement this way. module Text.Pandoc.Readers.Odt.Arrows.State where +import Prelude import Prelude hiding (foldl, foldr) import Control.Arrow import qualified Control.Category as Cat import Control.Monad -import Data.Foldable - import Text.Pandoc.Readers.Odt.Arrows.Utils import Text.Pandoc.Readers.Odt.Generic.Fallible diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs index e9ce53704..d3db3a9e2 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015 Martin Linnemann @@ -39,6 +40,7 @@ with an equivalent return value. -- We export everything module Text.Pandoc.Readers.Odt.Arrows.Utils where +import Prelude import Control.Arrow import Control.Monad (join) diff --git a/src/Text/Pandoc/Readers/Odt/Base.hs b/src/Text/Pandoc/Readers/Odt/Base.hs index 51c2da788..5e731aefe 100644 --- a/src/Text/Pandoc/Readers/Odt/Base.hs +++ b/src/Text/Pandoc/Readers/Odt/Base.hs @@ -1,5 +1,3 @@ - - {- Copyright (C) 2015 Martin Linnemann diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index ad0612ec8..78881914d 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Arrows #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE RecordWildCards #-} @@ -39,6 +40,7 @@ module Text.Pandoc.Readers.Odt.ContentReader , read_body ) where +import Prelude import Control.Applicative hiding (liftA, liftA2, liftA3) import Control.Arrow diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs index 03cb82f61..1fb5b5477 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- @@ -38,6 +39,7 @@ compatible instances of "ArrowChoice". -- We export everything module Text.Pandoc.Readers.Odt.Generic.Fallible where +import Prelude -- | Default for now. Will probably become a class at some point. type Failure = () diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs index 82ae3e20e..6d96897aa 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015 Martin Linnemann @@ -31,6 +32,7 @@ typesafe Haskell namespace identifiers and unsafe "real world" namespaces. module Text.Pandoc.Readers.Odt.Generic.Namespaces where +import Prelude import qualified Data.Map as M -- diff --git a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs index afd7d616c..b0543b6d1 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015 Martin Linnemann @@ -30,6 +31,7 @@ A map of values to sets of values. module Text.Pandoc.Readers.Odt.Generic.SetMap where +import Prelude import qualified Data.Map as M import qualified Data.Set as S diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs index 556517259..616d9290b 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TypeOperators #-} @@ -51,6 +52,7 @@ module Text.Pandoc.Readers.Odt.Generic.Utils , composition ) where +import Prelude import Control.Category (Category, (<<<), (>>>)) import qualified Control.Category as Cat (id) import Control.Monad (msum) diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs index 428048427..81392e16b 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Arrows #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE GADTs #-} @@ -67,6 +68,7 @@ module Text.Pandoc.Readers.Odt.Generic.XMLConverter , matchContent ) where +import Prelude import Control.Applicative hiding ( liftA, liftA2 ) import Control.Monad ( MonadPlus ) import Control.Arrow diff --git a/src/Text/Pandoc/Readers/Odt/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Namespaces.hs index 92e12931d..28865182f 100644 --- a/src/Text/Pandoc/Readers/Odt/Namespaces.hs +++ b/src/Text/Pandoc/Readers/Odt/Namespaces.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2015 Martin Linnemann @@ -31,6 +32,7 @@ Namespaces used in odt files. module Text.Pandoc.Readers.Odt.Namespaces ( Namespace (..) ) where +import Prelude import Data.List (isPrefixOf) import qualified Data.Map as M (empty, insert) import Data.Maybe (fromMaybe, listToMaybe) diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs index 477f6b8b7..e0444559b 100644 --- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs +++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE Arrows #-} {-# LANGUAGE RecordWildCards #-} @@ -57,6 +58,7 @@ module Text.Pandoc.Readers.Odt.StyleReader , readStylesAt ) where +import Prelude import Control.Applicative hiding (liftA, liftA2, liftA3) import Control.Arrow diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 292830bd2..75b99e079 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -27,6 +28,7 @@ Conversion of org-mode formatted plain text to 'Pandoc' document. -} module Text.Pandoc.Readers.Org ( readOrg ) where +import Prelude import Text.Pandoc.Readers.Org.Blocks (blockList, meta) import Text.Pandoc.Readers.Org.ParserState (optionsToParserState) import Text.Pandoc.Readers.Org.Parsing (OrgParser, readWithM) diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index 424102cb0..5dbce01bd 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -40,6 +41,7 @@ module Text.Pandoc.Readers.Org.BlockStarts , endOfBlock ) where +import Prelude import Control.Monad (void) import Text.Pandoc.Readers.Org.Parsing diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index de5cb007a..888cd9307 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -31,6 +32,7 @@ module Text.Pandoc.Readers.Org.Blocks , meta ) where +import Prelude import Text.Pandoc.Readers.Org.BlockStarts import Text.Pandoc.Readers.Org.DocumentTree (documentTree, headlineToBlocks) import Text.Pandoc.Readers.Org.Inlines diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index ae244e3b0..c9465581a 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -32,6 +33,7 @@ module Text.Pandoc.Readers.Org.DocumentTree , headlineToBlocks ) where +import Prelude import Control.Arrow ((***)) import Control.Monad (guard, void) import Data.Char (toLower, toUpper) diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs index 6a70c50b9..d02eb37c5 100644 --- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs +++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2016-2018 Albert Krewinkel @@ -29,6 +30,7 @@ module Text.Pandoc.Readers.Org.ExportSettings ( exportSettings ) where +import Prelude import Text.Pandoc.Readers.Org.ParserState import Text.Pandoc.Readers.Org.Parsing diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 6173669a5..91d3b7dd3 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Inlines , linkTarget ) where +import Prelude import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker) import Text.Pandoc.Readers.Org.ParserState import Text.Pandoc.Readers.Org.Parsing diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 6ad403fd8..938e393bb 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TupleSections #-} {- @@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Meta , metaLine ) where +import Prelude import Text.Pandoc.Readers.Org.BlockStarts import Text.Pandoc.Readers.Org.ExportSettings (exportSettings) import Text.Pandoc.Readers.Org.Inlines diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 6316766fa..4cb5bb626 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {- @@ -54,6 +55,7 @@ module Text.Pandoc.Readers.Org.ParserState , optionsToParserState ) where +import Prelude import Control.Monad.Reader (ReaderT, asks, local) import Data.Default (Default (..)) diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 36420478b..e014de65e 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -112,6 +113,7 @@ module Text.Pandoc.Readers.Org.Parsing , getPosition ) where +import Prelude import Text.Pandoc.Readers.Org.ParserState import Text.Pandoc.Parsing hiding (F, anyLine, blanklines, newline, diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index cba72cc07..07dbeca2a 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2014-2018 Albert Krewinkel @@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Shared , translateLang ) where +import Prelude import Data.Char (isAlphaNum) import Data.List (isPrefixOf, isSuffixOf) diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 91e0b057a..566f9b959 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -31,6 +32,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion from reStructuredText to 'Pandoc' document. -} module Text.Pandoc.Readers.RST ( readRST ) where +import Prelude import Control.Arrow (second) import Control.Monad (forM_, guard, liftM, mplus, mzero, when) import Control.Monad.Except (throwError) diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index 75e3f89eb..fba7e133e 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE RelaxedPolyRec #-} @@ -35,6 +36,7 @@ Conversion of twiki text to 'Pandoc' document. module Text.Pandoc.Readers.TWiki ( readTWiki ) where +import Prelude import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isAlphaNum) diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index fb0bbaa8a..7eef1b4dc 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2010-2012 Paul Rivier | tr '*#' '.@' 2010-2018 John MacFarlane @@ -52,6 +53,7 @@ TODO : refactor common patterns across readers : module Text.Pandoc.Readers.Textile ( readTextile) where +import Prelude import Control.Monad (guard, liftM) import Control.Monad.Except (throwError) import Data.Char (digitToInt, isUpper) diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs index a92f7bed2..55f53ef7f 100644 --- a/src/Text/Pandoc/Readers/TikiWiki.hs +++ b/src/Text/Pandoc/Readers/TikiWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} @@ -19,6 +20,7 @@ Conversion of TikiWiki text to 'Pandoc' document. module Text.Pandoc.Readers.TikiWiki ( readTikiWiki ) where +import Prelude import Control.Monad import Control.Monad.Except (throwError) import qualified Data.Foldable as F diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 64d219e9c..deac904b7 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2014 Matthew Pickering @@ -31,6 +32,7 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags ) where +import Prelude import Control.Monad (guard, void, when) import Control.Monad.Except (catchError, throwError) import Control.Monad.Reader (Reader, asks, runReader) diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs index b0d6fbb41..824a912c3 100644 --- a/src/Text/Pandoc/Readers/Vimwiki.hs +++ b/src/Text/Pandoc/Readers/Vimwiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {- Copyright (C) 2017-2018 Yuchen Pei @@ -64,6 +65,7 @@ Conversion of vimwiki text to 'Pandoc' document. module Text.Pandoc.Readers.Vimwiki ( readVimwiki ) where +import Prelude import Control.Monad (guard) import Control.Monad.Except (throwError) import Data.Default diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index d368b06c0..2aab015c2 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2011-2018 John MacFarlane @@ -31,6 +32,7 @@ offline, by incorporating linked images, CSS, and scripts into the HTML using data URIs. -} module Text.Pandoc.SelfContained ( makeDataURI, makeSelfContained ) where +import Prelude import Codec.Compression.GZip as Gzip import Control.Applicative ((<|>)) import Control.Monad.Except (throwError) diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index d76333f41..eb3addc43 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} @@ -100,6 +101,7 @@ module Text.Pandoc.Shared ( pandocVersion ) where +import Prelude import Codec.Archive.Zip import qualified Control.Exception as E import Control.Monad (MonadPlus (..), msum, unless) diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs index 9d63555c2..2f7d83527 100644 --- a/src/Text/Pandoc/Slides.hs +++ b/src/Text/Pandoc/Slides.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2012-2018 John MacFarlane @@ -29,6 +30,7 @@ Utility functions for splitting documents into slides for slide show formats (dzslides, revealjs, s5, slidy, slideous, beamer). -} module Text.Pandoc.Slides ( getSlideLevel, prepSlides ) where +import Prelude import Text.Pandoc.Definition -- | Find level of header that starts slides (defined as the least header diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 4be0d081c..6c3047263 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} @@ -38,6 +39,7 @@ module Text.Pandoc.Templates ( module Text.DocTemplates , getDefaultTemplate ) where +import Prelude import Control.Monad.Except (throwError) import Data.Aeson (ToJSON (..)) import qualified Data.Text as T diff --git a/src/Text/Pandoc/Translations.hs b/src/Text/Pandoc/Translations.hs index 8c38647b6..4a216af92 100644 --- a/src/Text/Pandoc/Translations.hs +++ b/src/Text/Pandoc/Translations.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} @@ -46,6 +47,7 @@ module Text.Pandoc.Translations ( , readTranslations ) where +import Prelude import Data.Aeson.Types (typeMismatch) import qualified Data.HashMap.Strict as HM import qualified Data.Map as M diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index 3f759958f..2bfda1ee8 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2010-2018 John MacFarlane diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs index 4d99324db..c1bae7038 100644 --- a/src/Text/Pandoc/UUID.hs +++ b/src/Text/Pandoc/UUID.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2010-2018 John MacFarlane @@ -31,6 +32,7 @@ in RFC4122. See http://tools.ietf.org/html/rfc4122 module Text.Pandoc.UUID ( UUID(..), getRandomUUID, getUUID ) where +import Prelude import Data.Bits (clearBit, setBit) import Data.Word import System.Random (RandomGen, getStdGen, randoms) diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index 596a8680e..5d4a9122a 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -82,6 +83,7 @@ module Text.Pandoc.Writers , getWriter ) where +import Prelude import Data.Aeson import qualified Data.ByteString.Lazy as BL import Data.List (intercalate) diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index f91fa8fa0..036185282 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -37,6 +38,7 @@ that it has omitted the construct. AsciiDoc: -} module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where +import Prelude import Control.Monad.State.Strict import Data.Aeson (Result (..), Value (String), fromJSON, toJSON) import Data.Char (isPunctuation, isSpace) diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 4abb77280..50224a715 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2015-2018 John MacFarlane @@ -32,6 +33,7 @@ CommonMark: -} module Text.Pandoc.Writers.CommonMark (writeCommonMark) where +import Prelude import CMarkGFM import Control.Monad.State.Strict (State, get, modify, runState) import Data.Foldable (foldrM) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index f94c12d89..10e996bdb 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- @@ -30,6 +31,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' format into ConTeXt. -} module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where +import Prelude import Control.Monad.State.Strict import Data.Char (ord, isDigit) import Data.List (intercalate, intersperse) diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 3daa8d0cf..53b321c7c 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {- Copyright (C) 2012-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to custom markup using a lua writer. -} module Text.Pandoc.Writers.Custom ( writeCustom ) where +import Prelude import Control.Arrow ((***)) import Control.Exception import Control.Monad (when) diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 3034fade5..f6e814095 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- @@ -30,6 +31,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to Docbook XML. -} module Text.Pandoc.Writers.Docbook ( writeDocbook4, writeDocbook5 ) where +import Prelude import Control.Monad.Reader import Data.Char (toLower) import Data.Generics (everywhere, mkT) diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 6422f61bf..82af18f7c 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -32,6 +33,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to docx. -} module Text.Pandoc.Writers.Docx ( writeDocx ) where +import Prelude import Codec.Archive.Zip import Control.Applicative ((<|>)) import Control.Monad.Except (catchError) diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index a74c23764..189bf138e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2008-2018 John MacFarlane @@ -39,6 +40,7 @@ DokuWiki: -} module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where +import Prelude import Control.Monad (zipWithM) import Control.Monad.Reader (ReaderT, ask, local, runReaderT) import Control.Monad.State.Strict (StateT, evalStateT) diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index cf50e9bb9..1dab2e627 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PatternGuards #-} @@ -32,6 +33,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to EPUB. -} module Text.Pandoc.Writers.EPUB ( writeEPUB2, writeEPUB3 ) where +import Prelude import Codec.Archive.Zip (Entry, addEntryToArchive, eRelativePath, emptyArchive, fromArchive, fromEntry, toEntry) import Control.Monad (mplus, unless, when, zipWithM) diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index e322c7d98..3f90f47b1 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {- @@ -37,6 +38,7 @@ FictionBook is an XML-based e-book format. For more information see: -} module Text.Pandoc.Writers.FB2 (writeFB2) where +import Prelude import Control.Monad (zipWithM) import Control.Monad.Except (catchError) import Control.Monad.State.Strict (StateT, evalStateT, get, lift, liftM, modify) diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 6e04abd52..80210c975 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -45,6 +46,7 @@ module Text.Pandoc.Writers.HTML ( writeRevealJs, tagWithAttributes ) where +import Prelude import Control.Monad.State.Strict import Data.Char (ord, toLower) import Data.List (intercalate, intersperse, isPrefixOf, partition) diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index dfa1d8b57..75b8c78dc 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -33,6 +34,7 @@ Conversion of 'Pandoc' documents to haddock markup. Haddock: -} module Text.Pandoc.Writers.Haddock (writeHaddock) where +import Prelude import Control.Monad.State.Strict import Data.Default import Data.Text (Text) diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index a5d851e40..a81ff96e3 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -16,6 +17,7 @@ InCopy is the companion word-processor to Adobe InDesign and ICML documents can into InDesign with File -> Place. -} module Text.Pandoc.Writers.ICML (writeICML) where +import Prelude import Control.Monad.Except (catchError) import Control.Monad.State.Strict import Data.List (intersperse, isInfixOf, isPrefixOf, stripPrefix) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 3b33e5a19..fb3236bd9 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- @@ -31,6 +32,7 @@ Reference: https://jats.nlm.nih.gov/publishing/tag-library -} module Text.Pandoc.Writers.JATS ( writeJATS ) where +import Prelude import Control.Monad.Reader import Data.Char (toLower) import Data.Generics (everywhere, mkT) diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 58a4c4d86..f354bc0a2 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -34,6 +35,7 @@ module Text.Pandoc.Writers.LaTeX ( writeLaTeX , writeBeamer ) where +import Prelude import Control.Applicative ((<|>)) import Control.Monad.State.Strict import Data.Aeson (FromJSON, object, (.=)) diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 1be955fe3..912231a88 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2007-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to groff man page format. -} module Text.Pandoc.Writers.Man ( writeMan) where +import Prelude import Control.Monad.State.Strict import Data.List (intercalate, intersperse, sort, stripPrefix) import qualified Data.Map as Map diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index cdd8f3b66..3bfa8a012 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -34,6 +35,7 @@ Conversion of 'Pandoc' documents to markdown-formatted plain text. Markdown: -} module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where +import Prelude import Control.Monad.Reader import Control.Monad.State.Strict import Data.Char (chr, isPunctuation, isSpace, ord, isAlphaNum) diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs index 477f5a0b1..99d17d594 100644 --- a/src/Text/Pandoc/Writers/Math.hs +++ b/src/Text/Pandoc/Writers/Math.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Text.Pandoc.Writers.Math ( texMathToInlines , convertMath @@ -6,6 +7,7 @@ module Text.Pandoc.Writers.Math ) where +import Prelude import Text.Pandoc.Class import Text.Pandoc.Definition import Text.Pandoc.Logging diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 2470d9200..df50028a0 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2008-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to MediaWiki markup. MediaWiki: -} module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki ) where +import Prelude import Control.Monad.Reader import Control.Monad.State.Strict import Data.List (intercalate) diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 558576876..cab44f817 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2007-2018 John MacFarlane @@ -36,6 +37,7 @@ TODO: -} module Text.Pandoc.Writers.Ms ( writeMs ) where +import Prelude import Control.Monad.State.Strict import Data.Char (isLower, isUpper, toUpper, ord) import Data.List (intercalate, intersperse, sort) diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 5dda951c5..2d53ca9a1 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2017-2018 Alexander Krotov @@ -42,6 +43,7 @@ However, @\@ tag is used for HTML raw blocks even though it is supported only in Emacs Muse. -} module Text.Pandoc.Writers.Muse (writeMuse) where +import Prelude import Control.Monad.State.Strict import Data.Text (Text) import Data.List (intersperse, transpose, isInfixOf) @@ -185,8 +187,8 @@ blockToMuse (OrderedList (start, style, _) items) = do -> [Block] -- ^ list item (list of blocks) -> StateT WriterState m Doc orderedListItemToMuse marker item = do - contents <- blockListToMuse item - return $ hang (length marker + 1) (text marker <> space) contents + contents <- blockListToMuse item + return $ hang (length marker + 1) (text marker <> space) contents blockToMuse (BulletList items) = do contents <- mapM bulletListItemToMuse items -- ensure that sublists have preceding blank line diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index f852bad96..730e3800a 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of a 'Pandoc' document to a string representation. -} module Text.Pandoc.Writers.Native ( writeNative ) where +import Prelude import Data.List (intersperse) import Data.Text (Text) import Text.Pandoc.Class (PandocMonad) diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 63a3f915a..7aecb3da5 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {- Copyright (C) 2008-2018 John MacFarlane @@ -29,6 +30,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to ODT. -} module Text.Pandoc.Writers.ODT ( writeODT ) where +import Prelude import Codec.Archive.Zip import Control.Monad.Except (catchError) import Control.Monad.State.Strict diff --git a/src/Text/Pandoc/Writers/OOXML.hs b/src/Text/Pandoc/Writers/OOXML.hs index b1eaa9d25..9e1c81964 100644 --- a/src/Text/Pandoc/Writers/OOXML.hs +++ b/src/Text/Pandoc/Writers/OOXML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2012-2018 John MacFarlane @@ -39,6 +40,7 @@ module Text.Pandoc.Writers.OOXML ( mknode , fitToPage ) where +import Prelude import Codec.Archive.Zip import Control.Monad.Reader import qualified Data.ByteString as B diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index 29e1bc80c..c081b957e 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {- Copyright (C) 2013-2018 John MacFarlane @@ -29,6 +30,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to OPML XML. -} module Text.Pandoc.Writers.OPML ( writeOPML) where +import Prelude import Control.Monad.Except (throwError) import Data.Text (Text, unpack) import qualified Data.Text as T diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 17edc0cbd..514327e9a 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} @@ -32,6 +33,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to OpenDocument XML. -} module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where +import Prelude import Control.Arrow ((***), (>>>)) import Control.Monad.State.Strict hiding (when) import Data.Char (chr) diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 2307204a5..a71775e13 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2010-2015 Puneeth Chaganti @@ -35,6 +36,7 @@ Conversion of 'Pandoc' documents to Emacs Org-Mode. Org-Mode: -} module Text.Pandoc.Writers.Org (writeOrg) where +import Prelude import Control.Monad.State.Strict import Data.Char (isAlphaNum, toLower) import Data.List (intersect, intersperse, isPrefixOf, partition, transpose) diff --git a/src/Text/Pandoc/Writers/Powerpoint.hs b/src/Text/Pandoc/Writers/Powerpoint.hs index 645a4cb86..665fd3f57 100644 --- a/src/Text/Pandoc/Writers/Powerpoint.hs +++ b/src/Text/Pandoc/Writers/Powerpoint.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- @@ -41,6 +42,7 @@ This is a wrapper around two modules: module Text.Pandoc.Writers.Powerpoint (writePowerpoint) where +import Prelude import Codec.Archive.Zip import Text.Pandoc.Definition import Text.Pandoc.Walk diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 410b6c20c..2ece78c01 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {- @@ -34,6 +35,7 @@ Text.Pandoc.Writers.Powerpoint.Presentation) to a zip archive. module Text.Pandoc.Writers.Powerpoint.Output ( presentationToArchive ) where +import Prelude import Control.Monad.Except (throwError, catchError) import Control.Monad.Reader import Control.Monad.State diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index fcd124e76..ac6001d2b 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {- @@ -57,6 +58,7 @@ module Text.Pandoc.Writers.Powerpoint.Presentation ( documentToPresentation ) where +import Prelude import Control.Monad.Reader import Control.Monad.State import Data.List (intercalate) diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 5c475ec23..74fc4dca4 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -31,6 +32,7 @@ Conversion of 'Pandoc' documents to reStructuredText. reStructuredText: -} module Text.Pandoc.Writers.RST ( writeRST ) where +import Prelude import Control.Monad.State.Strict import Data.Char (isSpace, toLower) import Data.List (isPrefixOf, stripPrefix) diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 7006b58d1..3045c1c10 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to RTF (rich text format). -} module Text.Pandoc.Writers.RTF ( writeRTF ) where +import Prelude import Control.Monad.Except (catchError, throwError) import Control.Monad import qualified Data.ByteString as B diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 964db5ecc..2edce7deb 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2013-2018 John MacFarlane @@ -44,6 +45,7 @@ module Text.Pandoc.Writers.Shared ( , stripLeadingTrailingSpace ) where +import Prelude import Control.Monad (zipWithM) import Data.Aeson (FromJSON (..), Result (..), ToJSON (..), Value (Object), encode, fromJSON) diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 4936c743e..e461f5715 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- @@ -30,6 +31,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to Docbook XML. -} module Text.Pandoc.Writers.TEI (writeTEI) where +import Prelude import Data.Char (toLower) import Data.List (isPrefixOf, stripPrefix) import Data.Text (Text) diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index bf434642e..305b41206 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2008-2018 John MacFarlane @@ -31,6 +32,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' format into Texinfo. -} module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where +import Prelude import Control.Monad.Except (throwError) import Control.Monad.State.Strict import Data.Char (chr, ord) diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index f46eb43bc..0ed79d2df 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2010-2018 John MacFarlane @@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to Textile markup. Textile: -} module Text.Pandoc.Writers.Textile ( writeTextile ) where +import Prelude import Control.Monad.State.Strict import Data.Char (isSpace) import Data.List (intercalate) diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index dec1f9d4a..a583b07b1 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2008-2018 John MacFarlane 2017-2018 Alex Ivkin @@ -32,6 +33,7 @@ http://zim-wiki.org/manual/Help/Wiki_Syntax.html -} module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where +import Prelude import Control.Monad (zipWithM) import Control.Monad.State.Strict (StateT, evalStateT, gets, modify) import Data.Default (Default (..)) diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index 62874f0b9..add46bd6c 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -36,6 +37,7 @@ module Text.Pandoc.XML ( escapeCharForXML, toEntities, fromEntities ) where +import Prelude import Data.Char (isAscii, isSpace, ord) import Data.Text (Text) import qualified Data.Text as T diff --git a/stack.yaml b/stack.yaml index b1fe59615..4add3e6a6 100644 --- a/stack.yaml +++ b/stack.yaml @@ -14,14 +14,11 @@ packages: - '.' extra-deps: - pandoc-citeproc-0.14.2 -- hslua-0.9.5 - skylighting-0.7.0.2 - skylighting-core-0.7.0.2 - ansi-terminal-0.7.1.1 - tasty-1.0.0.1 -- texmath-0.10.1.1 -- tagsoup-0.14.6 - pandoc-types-1.17.4.2 ghc-options: - "$locals": -fhide-source-paths -resolver: lts-10.3 + "$locals": -fhide-source-paths -XNoImplicitPrelude +resolver: lts-10.10 diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index de83d0639..89ea9a741 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Command (findPandoc, runTest, tests) where +import Prelude import Data.Algorithm.Diff import qualified Data.ByteString as BS import Data.List (isSuffixOf) diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 2a6543ea0..1c031aa64 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} -- Utility functions for the test suite. @@ -13,6 +14,7 @@ module Tests.Helpers ( test ) where +import Prelude import Data.Algorithm.Diff import qualified Data.Map as M import Data.Text (Text, unpack) diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index 5fe015265..b401e4e65 100644 --- a/test/Tests/Lua.hs +++ b/test/Tests/Lua.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Lua ( tests ) where +import Prelude import Control.Monad (when) import Data.Version (Version (versionBranch)) import System.FilePath (()) diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index ed4dcc076..f2b43640b 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Old (tests) where +import Prelude import Data.Algorithm.Diff import Prelude hiding (readFile) import System.Exit diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs index 3f60a523d..eb50b2b9a 100644 --- a/test/Tests/Readers/Creole.hs +++ b/test/Tests/Readers/Creole.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Creole (tests) where +import Prelude import Data.Text (Text) import qualified Data.Text as T import Test.Tasty diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index 9bbe85cba..4f2ad524a 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Readers.Docx (tests) where +import Prelude import Codec.Archive.Zip import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B diff --git a/test/Tests/Readers/EPUB.hs b/test/Tests/Readers/EPUB.hs index 1337a9c11..285efedbf 100644 --- a/test/Tests/Readers/EPUB.hs +++ b/test/Tests/Readers/EPUB.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Readers.EPUB (tests) where +import Prelude import qualified Data.ByteString.Lazy as BL import Test.Tasty import Test.Tasty.HUnit diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs index 70f33d2b2..f61f1f497 100644 --- a/test/Tests/Readers/HTML.hs +++ b/test/Tests/Readers/HTML.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.HTML (tests) where +import Prelude import Data.Text (Text) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Readers/JATS.hs b/test/Tests/Readers/JATS.hs index 5c7dfa77c..83c7c0da5 100644 --- a/test/Tests/Readers/JATS.hs +++ b/test/Tests/Readers/JATS.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.JATS (tests) where +import Prelude import Data.Text (Text) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 4396d550f..1538b6b0a 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.LaTeX (tests) where +import Prelude import Data.Text (Text) import qualified Data.Text as T import qualified Text.Pandoc.UTF8 as UTF8 diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index 1cd32b87d..0943aa4b1 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Markdown (tests) where +import Prelude import Data.Text (Text, unpack) import qualified Data.Text as T import Test.Tasty diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 89dbbc345..f1baa254d 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Muse (tests) where +import Prelude import Data.List (intersperse) import Data.Text (Text) import qualified Data.Text as T diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 4b7058cf9..c7f9a0725 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Readers.Odt (tests) where +import Prelude import Control.Monad (liftM) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs index 15dc63554..b1c86eada 100644 --- a/test/Tests/Readers/Org/Block.hs +++ b/test/Tests/Readers/Org/Block.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block (tests) where +import Prelude import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs index 8fa822089..a54ef6a17 100644 --- a/test/Tests/Readers/Org/Block/CodeBlock.hs +++ b/test/Tests/Readers/Org/Block/CodeBlock.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block.CodeBlock (tests) where +import Prelude import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) diff --git a/test/Tests/Readers/Org/Block/Figure.hs b/test/Tests/Readers/Org/Block/Figure.hs index cae6ef179..bead135e9 100644 --- a/test/Tests/Readers/Org/Block/Figure.hs +++ b/test/Tests/Readers/Org/Block/Figure.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block.Figure (tests) where +import Prelude import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:)) diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs index e8ad88558..3b0d7dda9 100644 --- a/test/Tests/Readers/Org/Block/Header.hs +++ b/test/Tests/Readers/Org/Block/Header.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block.Header (tests) where +import Prelude import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep, tagSpan) diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs index 343682a80..f273b684d 100644 --- a/test/Tests/Readers/Org/Block/List.hs +++ b/test/Tests/Readers/Org/Block/List.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block.List (tests) where +import Prelude import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs index db6e756f8..3cb6bb0f0 100644 --- a/test/Tests/Readers/Org/Block/Table.hs +++ b/test/Tests/Readers/Org/Block/Table.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Block.Table (tests) where +import Prelude import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs index 7e2c0fb8d..bb9c52e69 100644 --- a/test/Tests/Readers/Org/Directive.hs +++ b/test/Tests/Readers/Org/Directive.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Directive (tests) where +import Prelude import Data.Time (UTCTime (UTCTime), secondsToDiffTime) import Data.Time.Calendar (Day (ModifiedJulianDay)) import Test.Tasty (TestTree, testGroup) diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs index 9bf5556d2..07fe2d2e9 100644 --- a/test/Tests/Readers/Org/Inline.hs +++ b/test/Tests/Readers/Org/Inline.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Inline (tests) where +import Prelude import Data.List (intersperse) import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs index d7e38a6b0..c7974efa0 100644 --- a/test/Tests/Readers/Org/Inline/Citation.hs +++ b/test/Tests/Readers/Org/Inline/Citation.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Inline.Citation (tests) where +import Prelude import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:)) diff --git a/test/Tests/Readers/Org/Inline/Note.hs b/test/Tests/Readers/Org/Inline/Note.hs index 9eb1d02d6..1e0a59cb4 100644 --- a/test/Tests/Readers/Org/Inline/Note.hs +++ b/test/Tests/Readers/Org/Inline/Note.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Inline.Note (tests) where +import Prelude import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:)) diff --git a/test/Tests/Readers/Org/Inline/Smart.hs b/test/Tests/Readers/Org/Inline/Smart.hs index 77f10699d..b2889f8fe 100644 --- a/test/Tests/Readers/Org/Inline/Smart.hs +++ b/test/Tests/Readers/Org/Inline/Smart.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Inline.Smart (tests) where +import Prelude import Data.Text (Text) import Test.Tasty (TestTree) import Tests.Helpers ((=?>), purely, test) diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs index 6bd1b02e7..b17a05fe1 100644 --- a/test/Tests/Readers/Org/Meta.hs +++ b/test/Tests/Readers/Org/Meta.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Org.Meta (tests) where +import Prelude import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs index 5e8f6dd54..ea2a97e49 100644 --- a/test/Tests/Readers/Org/Shared.hs +++ b/test/Tests/Readers/Org/Shared.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Readers.Org.Shared ( (=:) , org @@ -5,6 +6,7 @@ module Tests.Readers.Org.Shared , tagSpan ) where +import Prelude import Data.List (intersperse) import Data.Text (Text) import Tests.Helpers (ToString, purely, test) diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs index 305c7060b..906ed4ff9 100644 --- a/test/Tests/Readers/RST.hs +++ b/test/Tests/Readers/RST.hs @@ -1,7 +1,9 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Tests.Readers.RST (tests) where +import Prelude import Data.Text (Text) import qualified Data.Text as T import Test.Tasty diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index e3646e95e..f0efbb02e 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Txt2Tags (tests) where +import Prelude import Data.List (intersperse) import Data.Text (Text) import qualified Data.Text as T diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs index cc448419c..85f7aae67 100644 --- a/test/Tests/Shared.hs +++ b/test/Tests/Shared.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Shared (tests) where +import Prelude import System.FilePath.Posix (joinPath) import Test.Tasty import Test.Tasty.HUnit (assertBool, testCase, (@?=)) diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs index 6b97c0761..d31d4ffe2 100644 --- a/test/Tests/Writers/AsciiDoc.hs +++ b/test/Tests/Writers/AsciiDoc.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Writers.AsciiDoc (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index 812aab4a6..fa1782391 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.ConTeXt (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs index 89ea76586..f6a047b0b 100644 --- a/test/Tests/Writers/Docbook.hs +++ b/test/Tests/Writers/Docbook.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Docbook (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs index 3ded0aa38..d17984d63 100644 --- a/test/Tests/Writers/Docx.hs +++ b/test/Tests/Writers/Docx.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Writers.Docx (tests) where +import Prelude import Text.Pandoc import Test.Tasty import Tests.Writers.OOXML diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs index 6663c42f8..5a04d9159 100644 --- a/test/Tests/Writers/FB2.hs +++ b/test/Tests/Writers/FB2.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.FB2 (tests) where +import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 23ff718d3..e771255b3 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.HTML (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs index 723c0e8a8..669220eea 100644 --- a/test/Tests/Writers/JATS.hs +++ b/test/Tests/Writers/JATS.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.JATS (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs index 471d9d9e7..00150022f 100644 --- a/test/Tests/Writers/LaTeX.hs +++ b/test/Tests/Writers/LaTeX.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.LaTeX (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs index 7f9ac3627..533be268a 100644 --- a/test/Tests/Writers/Markdown.hs +++ b/test/Tests/Writers/Markdown.hs @@ -1,7 +1,9 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Tests.Writers.Markdown (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index b86dee5e1..acd834173 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Writers.Muse (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs index 0c4bf7623..708b5069c 100644 --- a/test/Tests/Writers/Native.hs +++ b/test/Tests/Writers/Native.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Writers.Native (tests) where +import Prelude import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index bdfdea145..f2762ddfe 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -1,8 +1,10 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.OOXML (ooxmlTest) where +import Prelude import Text.Pandoc import Test.Tasty import Test.Tasty.Golden.Advanced diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs index 9cbe360da..c99f7344d 100644 --- a/test/Tests/Writers/Org.hs +++ b/test/Tests/Writers/Org.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Org (tests) where +import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs index ab09bca26..2a2eb4226 100644 --- a/test/Tests/Writers/Plain.hs +++ b/test/Tests/Writers/Plain.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Plain (tests) where +import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 9af8fc471..b5620ffdb 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Tests.Writers.Powerpoint (tests) where +import Prelude import Tests.Writers.OOXML (ooxmlTest) import Text.Pandoc import Test.Tasty diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index e54ce4737..64367a108 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.RST (tests) where +import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs index fa372909f..31e970495 100644 --- a/test/Tests/Writers/TEI.hs +++ b/test/Tests/Writers/TEI.hs @@ -1,6 +1,8 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.TEI (tests) where +import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 4cf1a952d..8613d5dda 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -1,7 +1,9 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -Wall #-} module Main where +import Prelude import GHC.IO.Encoding import Test.Tasty import qualified Tests.Command -- cgit v1.2.3 From d63bba30661182f15e56d07997ee0f7b539eb2ce Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 20 Mar 2018 11:15:43 +0300 Subject: Muse writer: escape "]" brackets in URLs as "%5D" --- src/Text/Pandoc/Writers/Muse.hs | 9 +++++++-- test/Tests/Writers/Muse.hs | 15 +++++++++++++++ 2 files changed, 22 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 2d53ca9a1..e72fcf52b 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -345,6 +345,11 @@ fixNotes (Space : n@Note{} : rest) = Str " " : n : fixNotes rest fixNotes (SoftBreak : n@Note{} : rest) = Str " " : n : fixNotes rest fixNotes (x:xs) = x : fixNotes xs +urlEscapeBrackets :: String -> String +urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs +urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs +urlEscapeBrackets [] = [] + -- | Convert list of Pandoc inline elements to Muse. inlineListToMuse :: PandocMonad m => [Inline] @@ -402,7 +407,7 @@ inlineToMuse (Link _ txt (src, _)) = return $ "[[" <> text (escapeLink x) <> "]]" _ -> do contents <- inlineListToMuse txt return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]" - where escapeLink lnk = if isImageUrl lnk then "URL:" ++ lnk else lnk + where escapeLink lnk = if isImageUrl lnk then "URL:" ++ urlEscapeBrackets lnk else urlEscapeBrackets lnk -- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el imageExtensions = [".eps", ".gif", ".jpg", ".jpeg", ".pbm", ".png", ".tiff", ".xbm", ".xpm"] isImageUrl = (`elem` imageExtensions) . takeExtension @@ -419,7 +424,7 @@ inlineToMuse (Image attr inlines (source, title)) = do let width = case dimension Width attr of Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" - return $ "[[" <> text (source ++ width) <> "]" <> title' <> "]" + return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index acd834173..2728fd9f9 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -372,6 +372,21 @@ tests = [ testGroup "block elements" =?> "[[URL:1.png][Link to image]]" , "link to image without description" =: link "1.png" "" (str "1.png") =?> "[[URL:1.png]]" + + , testGroup "escape brackets in links" + [ "link with description" + =: link "https://example.com/foo].txt" "" (str "Description") + =?> "[[https://example.com/foo%5D.txt][Description]]" + , "link without description" + =: link "https://example.com/foo].txt" "" (str "https://example.com/foo].txt") + =?> "[[https://example.com/foo%5D.txt][https://example.com/foo].txt]]" + , "image link with description" + =: link "foo]bar.png" "" (str "Image link") + =?> "[[URL:foo%5Dbar.png][Image link]]" + , "image link without description" + =: link "foo]bar.png" "" (str "foo]bar.png") + =?> "[[URL:foo%5Dbar.png][foo]bar.png]]" + ] ] , "image" =: image "image.png" "Image 1" (str "") =?> "[[image.png][Image 1]]" , "image with width" =: -- cgit v1.2.3 From 268c73c873b93daf3321d38d659be7849579c7f0 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 20 Mar 2018 11:24:19 +0300 Subject: Muse writer: escape ";" to avoid accidental comments --- src/Text/Pandoc/Writers/Muse.hs | 3 ++- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 3 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index e72fcf52b..eb1821922 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -290,7 +290,8 @@ conditionalEscapeString s = "::" `isInfixOf` s || "----" `isInfixOf` s || "~~" `isInfixOf` s || - "-" == s + "-" == s || + ";" == s then escapeString s else s diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 2728fd9f9..04f6de449 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -321,6 +321,7 @@ tests = [ testGroup "block elements" , "" , " - bar" ] + , "escape ; to avoid accidental comments" =: text "; foo" =?> "; foo" ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" -- cgit v1.2.3 From bc0025d944d936ab4f311e10992b7c5802424446 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 20 Mar 2018 13:20:01 +0300 Subject: Muse writer: remove key-value pairs from attributes before normalization --- src/Text/Pandoc/Writers/Muse.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index eb1821922..b64756f91 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -312,6 +312,13 @@ replaceSmallCaps :: Inline -> Inline replaceSmallCaps (SmallCaps lst) = Emph lst replaceSmallCaps x = x +removeKeyValues :: Inline -> Inline +removeKeyValues (Code (i, cls, _) xs) = Code (i, cls, []) xs +-- Do not remove attributes from Link +-- Do not remove attributes, such as "width", from Image +removeKeyValues (Span (i, cls, _) xs) = Span (i, cls, []) xs +removeKeyValues x = x + normalizeInlineList :: [Inline] -> [Inline] normalizeInlineList (Str "" : xs) = normalizeInlineList xs @@ -356,7 +363,7 @@ inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc inlineListToMuse lst = do - lst' <- normalizeInlineList <$> preprocessInlineList (map replaceSmallCaps lst) + lst' <- normalizeInlineList <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) if null lst' then pure "" else hcat <$> mapM inlineToMuse (fixNotes lst') -- cgit v1.2.3 From 81afcdfaf808d345cc94facdcf927f87325dfa4e Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 20 Mar 2018 15:01:53 +0300 Subject: Muse writer: escape "]" in image title --- src/Text/Pandoc/Writers/Muse.hs | 3 ++- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 3 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index b64756f91..8feb277c6 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -428,11 +428,12 @@ inlineToMuse (Image attr inlines (source, title)) = do then if null inlines then "" else "[" <> alt <> "]" - else "[" <> text title <> "]" + else "[" <> text (escape title) <> "]" let width = case dimension Width attr of Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" + where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString s inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 04f6de449..ad7e4f1c4 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -393,6 +393,7 @@ tests = [ testGroup "block elements" , "image with width" =: imageWith ("", [], [("width", "60%")]) "image.png" "Image" (str "") =?> "[[image.png 60][Image]]" + , "escape brackets in image title" =: image "image.png" "Foo]bar" (str "") =?> "[[image.png][Foo]bar]]" , "note" =: note (plain (text "Foo")) =?> unlines [ "[1]" , "" -- cgit v1.2.3 From 6f507336918baa016eefce854f00fad1e1a78068 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 21 Mar 2018 17:32:12 +0300 Subject: Muse writer: don't align ordered list items It leads to problems with round-trip test, because aligned line blocks can't be read back. --- src/Text/Pandoc/Writers/Muse.hs | 5 +---- test/Tests/Writers/Muse.hs | 12 ++++++------ test/writer.muse | 6 +++--- 3 files changed, 10 insertions(+), 13 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 8feb277c6..ad3afd751 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -175,10 +175,7 @@ blockToMuse (BlockQuote blocks) = do blockToMuse (OrderedList (start, style, _) items) = do let markers = take (length items) $ orderedListMarkers (start, style, Period) - let maxMarkerLength = maximum $ map length markers - let markers' = map (\m -> let s = maxMarkerLength - length m - in m ++ replicate s ' ') markers - contents <- zipWithM orderedListItemToMuse markers' items + contents <- zipWithM orderedListItemToMuse markers items -- ensure that sublists have preceding blank line topLevel <- gets stTopLevel return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index ad7e4f1c4..56fa22955 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -74,8 +74,8 @@ tests = [ testGroup "block elements" , plain $ text "second" , plain $ text "third" ] - =?> unlines [ " I. first" - , " II. second" + =?> unlines [ " I. first" + , " II. second" , " III. third" ] , "bullet list" =: bulletList [ plain $ text "first" @@ -138,11 +138,11 @@ tests = [ testGroup "block elements" orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> - unlines [ " I. First" + unlines [ " I. First" , " II. Second" , "" , "" - , " I. Third" + , " I. Third" , " II. Fourth" ] , "ordered lists with equal styles" =: @@ -169,7 +169,7 @@ tests = [ testGroup "block elements" unlines [ " - First" , " - Second" , "" - , " I. Third" + , " I. Third" , " II. Fourth" ] , "different style ordered lists" =: @@ -179,7 +179,7 @@ tests = [ testGroup "block elements" orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> - unlines [ " I. First" + unlines [ " I. First" , " II. Second" , "" , " 1. Third" diff --git a/test/writer.muse b/test/writer.muse index 5db3871a1..530fb3ba5 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -224,9 +224,9 @@ Same thing but with paragraphs: with a continuation iv. sublist with roman numerals, starting with 4 - v. more items - A. a subsublist - B. a subsublist + v. more items + A. a subsublist + B. a subsublist Nesting: -- cgit v1.2.3 From d58b961a6d83a9f3a815d7aa281c692281954a00 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sat, 24 Mar 2018 23:51:38 +0300 Subject: Muse writer: do not join Span's doing normalization Separate spans may have different semantics, for example if spans indicate syllables in a word. --- src/Text/Pandoc/Writers/Muse.hs | 3 +-- test/Tests/Writers/Muse.hs | 3 +++ 2 files changed, 4 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index ad3afd751..6ecd826fa 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -339,8 +339,7 @@ normalizeInlineList (Code _ x1 : Code _ x2 : ils) = normalizeInlineList $ Code nullAttr (x1 ++ x2) : ils normalizeInlineList (RawInline f1 x1 : RawInline f2 x2 : ils) | f1 == f2 = normalizeInlineList $ RawInline f1 (x1 ++ x2) : ils -normalizeInlineList (Span a1 x1 : Span a2 x2 : ils) | a1 == a2 - = normalizeInlineList $ Span a1 (x1 ++ x2) : ils +-- Do not join Span's during normalization normalizeInlineList (x:xs) = x : normalizeInlineList xs normalizeInlineList [] = [] diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 56fa22955..1218bc7c9 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -405,6 +405,9 @@ tests = [ testGroup "block elements" =?> "#anchor Foo bar" , "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar") =?> "#anchor bar" + , "adjacent spans" =: spanWith ("", ["syllable"], []) (str "wa") <> + spanWith ("", ["syllable"], []) (str "ter") + =?> "water" , testGroup "combined" [ "emph word before" =: para (text "foo" <> emph (text "bar")) =?> -- cgit v1.2.3 From 4a8993f9b008a0ff223b5a1e283ae9e21a66c5c0 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 25 Mar 2018 01:18:33 +0300 Subject: Muse writer: improve span writing Test more cases when span has or hasn't anchor, class and contents in different combinations. --- src/Text/Pandoc/Writers/Muse.hs | 8 +++++--- test/Tests/Writers/Muse.hs | 10 ++++++++-- 2 files changed, 13 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 6ecd826fa..128e2c6f9 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -441,6 +441,8 @@ inlineToMuse (Span (anchor,names,_) inlines) = do let anchorDoc = if null anchor then mempty else text ('#':anchor) <> space - return $ anchorDoc <> if null names - then contents - else " text (head names) <> "\">" <> contents <> "" + return $ anchorDoc <> (if null inlines && not (null anchor) + then mempty + else (if null names + then "" + else " text (head names) <> "\">") <> contents <> "") diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 1218bc7c9..c3a6a9d62 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -400,9 +400,15 @@ tests = [ testGroup "block elements" , "[1] Foo" ] , "span with class" =: spanWith ("",["foobar"],[]) (text "Some text") - =?> "Some text" - , "span with anchor" =: spanWith ("anchor", [], []) (text "Foo bar") + =?> "Some text" + , "span without class" =: spanWith ("",[],[]) (text "Some text") + =?> "Some text" + , "span with anchor" =: spanWith ("anchor", [], []) (mempty) <> (text "Foo bar") =?> "#anchor Foo bar" + , "empty span with anchor" =: spanWith ("anchor", [], []) (mempty) + =?> "#anchor" + , "empty span without class and anchor" =: spanWith ("", [], []) (mempty) + =?> "" , "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar") =?> "#anchor bar" , "adjacent spans" =: spanWith ("", ["syllable"], []) (str "wa") <> -- cgit v1.2.3 From a3f659d2c0bccd01d2eceba8756c728f90d4f231 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 25 Mar 2018 18:11:38 +0300 Subject: Muse writer: escape ordered list markers Also reduced amount of tags in output to avoid escaping every "-" and word that ends in a full stop. --- src/Text/Pandoc/Writers/Muse.hs | 66 ++++++++++++++++++++++++++++++++--------- test/Tests/Writers/Muse.hs | 9 +++--- test/writer.muse | 4 +-- 3 files changed, 59 insertions(+), 20 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 128e2c6f9..5f9b58aa1 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -45,6 +45,7 @@ even though it is supported only in Emacs Muse. module Text.Pandoc.Writers.Muse (writeMuse) where import Prelude import Control.Monad.State.Strict +import Data.Char (isSpace, isDigit, isAsciiUpper, isAsciiLower) import Data.Text (Text) import Data.List (intersperse, transpose, isInfixOf) import System.FilePath (takeExtension) @@ -153,9 +154,9 @@ blockListToMuse blocks = do blockToMuse :: PandocMonad m => Block -- ^ Block element -> StateT WriterState m Doc -blockToMuse (Plain inlines) = inlineListToMuse inlines +blockToMuse (Plain inlines) = inlineListToMuse' inlines blockToMuse (Para inlines) = do - contents <- inlineListToMuse inlines + contents <- inlineListToMuse' inlines return $ contents <> blankline blockToMuse (LineBlock lns) = do lns' <- mapM inlineListToMuse lns @@ -206,7 +207,7 @@ blockToMuse (DefinitionList items) = do => ([Inline], [[Block]]) -> StateT WriterState m Doc definitionListItemToMuse (label, defs) = do - label' <- inlineListToMuse label + label' <- inlineListToMuse' label contents <- liftM vcat $ mapM descriptionToMuse defs let ind = offset label' return $ hang ind label' contents @@ -280,15 +281,23 @@ escapeString s = substitute "" "</verbatim>" s ++ "" +startsWithMarker :: (Char -> Bool) -> String -> Bool +startsWithMarker f (' ':xs) = startsWithMarker f xs +startsWithMarker f (x:xs) = + f x && (startsWithMarker f xs || startsWithDot xs) + where + startsWithDot ('.':[]) = True + startsWithDot ('.':c:_) = isSpace c + startsWithDot _ = False +startsWithMarker _ [] = False + -- | Escape special characters for Muse if needed. conditionalEscapeString :: String -> String conditionalEscapeString s = if any (`elem` ("#*<=>[]|" :: String)) s || "::" `isInfixOf` s || "----" `isInfixOf` s || - "~~" `isInfixOf` s || - "-" == s || - ";" == s + "~~" `isInfixOf` s then escapeString s else s @@ -354,15 +363,44 @@ urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs urlEscapeBrackets [] = [] --- | Convert list of Pandoc inline elements to Muse. -inlineListToMuse :: PandocMonad m - => [Inline] +fixOrEscape :: Inline -> Bool +fixOrEscape (Str "-") = True -- TODO: " - " should be escaped too +fixOrEscape (Str ";") = True +fixOrEscape (Str s) = startsWithMarker isDigit s || + startsWithMarker isAsciiLower s || + startsWithMarker isAsciiUpper s +fixOrEscape (Space) = True +fixOrEscape (SoftBreak) = True +fixOrEscape _ = False + +-- | Convert list of Pandoc inline elements to Muse +renderInlineList :: PandocMonad m + => Bool + -> [Inline] -> StateT WriterState m Doc -inlineListToMuse lst = do - lst' <- normalizeInlineList <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) - if null lst' - then pure "" - else hcat <$> mapM inlineToMuse (fixNotes lst') +renderInlineList True [] = pure "" +renderInlineList False [] = pure "" +renderInlineList start lst@(x:xs) = do r <- inlineToMuse x + opts <- gets stOptions + lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs --hcat <$> mapM inlineToMuse xs + if start && fixOrEscape x + then pure ((text "") <> r <> lst') + else pure (r <> lst') + +-- | Normalize and convert list of Pandoc inline elements to Muse. +inlineListToMuse'' :: PandocMonad m + => Bool + -> [Inline] + -> StateT WriterState m Doc +inlineListToMuse'' start lst = do + lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) + renderInlineList start lst' + +inlineListToMuse' :: PandocMonad m => [Inline] -> StateT WriterState m Doc +inlineListToMuse' = inlineListToMuse'' True + +inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc +inlineListToMuse = inlineListToMuse'' False -- | Convert Pandoc inline element to Muse. inlineToMuse :: PandocMonad m diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 3c5d1511a..1412739cb 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -312,16 +312,17 @@ tests = [ testGroup "block elements" -- We don't want colons to be escaped if they can't be confused -- with definition list item markers. , "do not escape colon" =: str ":" =?> ":" - , "escape - to avoid accidental unordered lists" =: text " - foo" =?> " - foo" + , "escape - to avoid accidental unordered lists" =: text " - foo" =?> " - foo" , "escape - inside a list to avoid accidental nested unordered lists" =: bulletList [ (para $ text "foo") <> (para $ text "- bar") ] =?> unlines [ " - foo" , "" - , " - bar" + , " - bar" ] - , "escape ; to avoid accidental comments" =: text "; foo" =?> "; foo" + , "escape ; to avoid accidental comments" =: text "; foo" =?> "; foo" + , "escape ; after softbreak" =: text "foo" <> softbreak <> text "; bar" =?> "foo\n; bar" ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" @@ -408,7 +409,7 @@ tests = [ testGroup "block elements" , "empty span with anchor" =: spanWith ("anchor", [], []) (mempty) =?> "#anchor" , "empty span without class and anchor" =: spanWith ("", [], []) (mempty) - =?> "" + =?> "" , "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar") =?> "#anchor bar" , "adjacent spans" =: spanWith ("", ["syllable"], []) (str "wa") <> diff --git a/test/writer.muse b/test/writer.muse index 530fb3ba5..fe278af65 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -245,7 +245,7 @@ Should not be a list item: M.A. 2007 -B. Williams +B. Williams ---- @@ -594,7 +594,7 @@ Bang: ! Plus: + -Minus: - +Minus: - ---- -- cgit v1.2.3 From 989a9ebec3e813f6f1663ca0b5d064acc3335a4a Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 25 Mar 2018 23:42:07 +0300 Subject: Muse writer: remove unused binding --- src/Text/Pandoc/Writers/Muse.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 5f9b58aa1..af71405f3 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -380,12 +380,12 @@ renderInlineList :: PandocMonad m -> StateT WriterState m Doc renderInlineList True [] = pure "" renderInlineList False [] = pure "" -renderInlineList start lst@(x:xs) = do r <- inlineToMuse x - opts <- gets stOptions - lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs --hcat <$> mapM inlineToMuse xs - if start && fixOrEscape x - then pure ((text "") <> r <> lst') - else pure (r <> lst') +renderInlineList start (x:xs) = do r <- inlineToMuse x + opts <- gets stOptions + lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs --hcat <$> mapM inlineToMuse xs + if start && fixOrEscape x + then pure ((text "") <> r <> lst') + else pure (r <> lst') -- | Normalize and convert list of Pandoc inline elements to Muse. inlineListToMuse'' :: PandocMonad m -- cgit v1.2.3 From 6d3509053884b65c57dc5dadade80316d07a44d8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 26 Mar 2018 12:21:02 +0300 Subject: Cleanup Muse reader and writer --- src/Text/Pandoc/Readers/Muse.hs | 56 ++++++++++++++--------------------------- src/Text/Pandoc/Writers/Muse.hs | 10 ++++---- 2 files changed, 24 insertions(+), 42 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 3e6130585..b43a53d60 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -1,5 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TupleSections #-} {- Copyright (C) 2017-2018 Alexander Krotov @@ -174,7 +175,7 @@ parseHtmlContent tag = try $ do pos <- getPosition (TagOpen _ attr, _) <- htmlTag (~== TagOpen tag []) manyTill spaceChar eol - content <- parseBlocksTill (try $ ((count (sourceColumn pos - 1) spaceChar) >> endtag)) + content <- parseBlocksTill $ try $ count (sourceColumn pos - 1) spaceChar >> endtag manyTill spaceChar eol -- closing tag must be followed by optional whitespace and newline return (htmlAttrToPandoc attr, content) where @@ -274,9 +275,7 @@ parseBlocksTill end = paraStart) where parseEnd = mempty <$ end - blockStart = do first <- blockElements - rest <- continuation - return $ first B.<> rest + blockStart = (B.<>) <$> blockElements <*> continuation listStart = do updateState (\st -> st { museInPara = False }) (first, e) <- anyListUntil ((Left <$> end) <|> (Right <$> continuation)) @@ -299,10 +298,8 @@ listItemContentsUntil col pre end = try listStart <|> try paraStart where - parsePre = do e <- pre - return (mempty, e) - parseEnd = do e <- end - return (mempty, e) + parsePre = (mempty,) <$> pre + parseEnd = (mempty,) <$> end paraStart = do (first, e) <- paraUntil ((Left <$> pre) <|> (Right <$> continuation) <|> (Left <$> end)) case e of @@ -468,9 +465,7 @@ paraUntil end = do noteMarker :: PandocMonad m => MuseParser m String noteMarker = try $ do char '[' - first <- oneOf "123456789" - rest <- manyTill digit (char ']') - return $ first:rest + (:) <$> oneOf "123456789" <*> manyTill digit (char ']') -- Amusewiki version of note -- Parsing is similar to list item, except that note marker is used instead of list marker @@ -713,11 +708,7 @@ elementsToTable = foldM museAppendElement emptyTable where emptyTable = MuseTable mempty mempty mempty mempty table :: PandocMonad m => MuseParser m (F Blocks) -table = try $ do - rows <- tableElements - let tbl = elementsToTable rows - let pandocTbl = museToPandocTable <$> tbl :: F Blocks - return pandocTbl +table = try $ fmap museToPandocTable <$> (elementsToTable <$> tableElements) tableParseElement :: PandocMonad m => MuseParser m MuseTableElement tableParseElement = tableParseHeader @@ -831,16 +822,14 @@ enclosedInlines start end = try $ trimInlinesF . mconcat <$> (enclosed (atStart start) end inline <* notFollowedBy (satisfy isLetter)) inlineTag :: PandocMonad m - => (Inlines -> Inlines) - -> String + => String -> MuseParser m (F Inlines) -inlineTag f tag = try $ do +inlineTag tag = try $ do htmlTag (~== TagOpen tag []) - res <- manyTill inline (void $ htmlTag (~== TagClose tag)) - return $ f <$> mconcat res + mconcat <$> manyTill inline (void $ htmlTag (~== TagClose tag)) strongTag :: PandocMonad m => MuseParser m (F Inlines) -strongTag = inlineTag B.strong "strong" +strongTag = fmap B.strong <$> inlineTag "strong" strong :: PandocMonad m => MuseParser m (F Inlines) strong = fmap B.strong <$> emphasisBetween (string "**") @@ -854,16 +843,16 @@ underlined = do fmap underlineSpan <$> emphasisBetween (char '_') emphTag :: PandocMonad m => MuseParser m (F Inlines) -emphTag = inlineTag B.emph "em" +emphTag = fmap B.emph <$> inlineTag "em" superscriptTag :: PandocMonad m => MuseParser m (F Inlines) -superscriptTag = inlineTag B.superscript "sup" +superscriptTag = fmap B.superscript <$> inlineTag "sup" subscriptTag :: PandocMonad m => MuseParser m (F Inlines) -subscriptTag = inlineTag B.subscript "sub" +subscriptTag = fmap B.subscript <$> inlineTag "sub" strikeoutTag :: PandocMonad m => MuseParser m (F Inlines) -strikeoutTag = inlineTag B.strikeout "del" +strikeoutTag = fmap B.strikeout <$> inlineTag "del" verbatimTag :: PandocMonad m => MuseParser m (F Inlines) verbatimTag = return . B.text . snd <$> htmlElement "verbatim" @@ -891,9 +880,7 @@ code = try $ do return $ return $ B.code contents codeTag :: PandocMonad m => MuseParser m (F Inlines) -codeTag = do - (attrs, content) <- htmlElement "code" - return $ return $ B.codeWith attrs content +codeTag = return . uncurry B.codeWith <$> htmlElement "code" inlineLiteralTag :: PandocMonad m => MuseParser m (F Inlines) inlineLiteralTag = @@ -904,10 +891,7 @@ inlineLiteralTag = rawInline (attrs, content) = B.rawInline (format attrs) content str :: PandocMonad m => MuseParser m (F Inlines) -str = do - result <- many1 alphaNum - updateLastStrPos - return $ return $ B.str result +str = return . B.str <$> many1 alphaNum <* updateLastStrPos symbol :: PandocMonad m => MuseParser m (F Inlines) symbol = return . B.str <$> count 1 nonspaceChar @@ -929,9 +913,7 @@ link = try $ do isImageUrl = (`elem` imageExtensions) . takeExtension linkContent :: PandocMonad m => MuseParser m (F Inlines) -linkContent = do - char '[' - trimInlinesF . mconcat <$> manyTill inline (string "]") +linkContent = char '[' >> trimInlinesF . mconcat <$> manyTill inline (string "]") linkText :: PandocMonad m => MuseParser m (String, String, Maybe (F Inlines)) linkText = do diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index af71405f3..c4614113c 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -286,7 +286,7 @@ startsWithMarker f (' ':xs) = startsWithMarker f xs startsWithMarker f (x:xs) = f x && (startsWithMarker f xs || startsWithDot xs) where - startsWithDot ('.':[]) = True + startsWithDot ['.'] = True startsWithDot ('.':c:_) = isSpace c startsWithDot _ = False startsWithMarker _ [] = False @@ -369,8 +369,8 @@ fixOrEscape (Str ";") = True fixOrEscape (Str s) = startsWithMarker isDigit s || startsWithMarker isAsciiLower s || startsWithMarker isAsciiUpper s -fixOrEscape (Space) = True -fixOrEscape (SoftBreak) = True +fixOrEscape Space = True +fixOrEscape SoftBreak = True fixOrEscape _ = False -- | Convert list of Pandoc inline elements to Muse @@ -382,9 +382,9 @@ renderInlineList True [] = pure "" renderInlineList False [] = pure "" renderInlineList start (x:xs) = do r <- inlineToMuse x opts <- gets stOptions - lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs --hcat <$> mapM inlineToMuse xs + lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs if start && fixOrEscape x - then pure ((text "") <> r <> lst') + then pure (text "" <> r <> lst') else pure (r <> lst') -- | Normalize and convert list of Pandoc inline elements to Muse. -- cgit v1.2.3 From b379a2903a07fc6a7389d1fed40565b3551fecc5 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Mar 2018 13:17:04 +0300 Subject: Muse writer: escape semicolons and markers after line break --- src/Text/Pandoc/Writers/Muse.hs | 2 +- test/Tests/Writers/Muse.hs | 1 + test/writer.muse | 2 +- 3 files changed, 3 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index c4614113c..5b08f0d63 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -382,7 +382,7 @@ renderInlineList True [] = pure "" renderInlineList False [] = pure "" renderInlineList start (x:xs) = do r <- inlineToMuse x opts <- gets stOptions - lst' <- renderInlineList (x == SoftBreak && writerWrapText opts == WrapPreserve) xs + lst' <- renderInlineList ((x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak) xs if start && fixOrEscape x then pure (text "" <> r <> lst') else pure (r <> lst') diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 1412739cb..c1bec1ba2 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -323,6 +323,7 @@ tests = [ testGroup "block elements" ] , "escape ; to avoid accidental comments" =: text "; foo" =?> "; foo" , "escape ; after softbreak" =: text "foo" <> softbreak <> text "; bar" =?> "foo\n; bar" + , "escape ; after linebreak" =: text "foo" <> linebreak <> text "; bar" =?> "foo
\n; bar" ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" diff --git a/test/writer.muse b/test/writer.muse index fe278af65..abb6b63fe 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -42,7 +42,7 @@ item. Here’s one with a bullet. * criminey. There should be a hard line break
-here. +here. ---- -- cgit v1.2.3 From 72527770783ac098e6ec9976eebcd3f8401700cc Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Mar 2018 14:53:03 +0300 Subject: Muse writer: define Muse type --- src/Text/Pandoc/Writers/Muse.hs | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 5b08f0d63..1257a3f06 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -69,6 +69,8 @@ data WriterState = , stIds :: Set.Set String } +type Muse = StateT WriterState + -- | Convert Pandoc to Muse. writeMuse :: PandocMonad m => WriterOptions @@ -86,7 +88,7 @@ writeMuse opts document = -- | Return Muse representation of document. pandocToMuse :: PandocMonad m => Pandoc - -> StateT WriterState m Text + -> Muse m Text pandocToMuse (Pandoc meta blocks) = do opts <- gets stOptions let colwidth = if writerWrapText opts == WrapAuto @@ -111,7 +113,7 @@ pandocToMuse (Pandoc meta blocks) = do catWithBlankLines :: PandocMonad m => [Block] -- ^ List of block elements -> Int -- ^ Number of blank lines - -> StateT WriterState m Doc + -> Muse m Doc catWithBlankLines (b : bs) n = do b' <- blockToMuse b bs' <- flatBlockListToMuse bs @@ -122,7 +124,7 @@ catWithBlankLines _ _ = error "Expected at least one block" -- | without setting stTopLevel. flatBlockListToMuse :: PandocMonad m => [Block] -- ^ List of block elements - -> StateT WriterState m Doc + -> Muse m Doc flatBlockListToMuse bs@(BulletList _ : BulletList _ : _) = catWithBlankLines bs 2 flatBlockListToMuse bs@(OrderedList (_, style1, _) _ : OrderedList (_, style2, _) _ : _) = catWithBlankLines bs (if style1' == style2' then 2 else 0) @@ -138,7 +140,7 @@ flatBlockListToMuse [] = return mempty -- | Convert list of Pandoc block elements to Muse. blockListToMuse :: PandocMonad m => [Block] -- ^ List of block elements - -> StateT WriterState m Doc + -> Muse m Doc blockListToMuse blocks = do oldState <- get modify $ \s -> s { stTopLevel = not $ stInsideBlock s @@ -153,7 +155,7 @@ blockListToMuse blocks = do -- | Convert Pandoc block element to Muse. blockToMuse :: PandocMonad m => Block -- ^ Block element - -> StateT WriterState m Doc + -> Muse m Doc blockToMuse (Plain inlines) = inlineListToMuse' inlines blockToMuse (Para inlines) = do contents <- inlineListToMuse' inlines @@ -183,7 +185,7 @@ blockToMuse (OrderedList (start, style, _) items) = do where orderedListItemToMuse :: PandocMonad m => String -- ^ marker for list item -> [Block] -- ^ list item (list of blocks) - -> StateT WriterState m Doc + -> Muse m Doc orderedListItemToMuse marker item = do contents <- blockListToMuse item return $ hang (length marker + 1) (text marker <> space) contents @@ -194,7 +196,7 @@ blockToMuse (BulletList items) = do return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where bulletListItemToMuse :: PandocMonad m => [Block] - -> StateT WriterState m Doc + -> Muse m Doc bulletListItemToMuse item = do contents <- blockListToMuse item return $ hang 2 "- " contents @@ -205,7 +207,7 @@ blockToMuse (DefinitionList items) = do return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where definitionListItemToMuse :: PandocMonad m => ([Inline], [[Block]]) - -> StateT WriterState m Doc + -> Muse m Doc definitionListItemToMuse (label, defs) = do label' <- inlineListToMuse' label contents <- liftM vcat $ mapM descriptionToMuse defs @@ -213,7 +215,7 @@ blockToMuse (DefinitionList items) = do return $ hang ind label' contents descriptionToMuse :: PandocMonad m => [Block] - -> StateT WriterState m Doc + -> Muse m Doc descriptionToMuse desc = hang 4 " :: " <$> blockListToMuse desc blockToMuse (Header level (ident,_,_) inlines) = do opts <- gets stOptions @@ -261,14 +263,14 @@ blockToMuse Null = return empty -- | Return Muse representation of notes. notesToMuse :: PandocMonad m => Notes - -> StateT WriterState m Doc + -> Muse m Doc notesToMuse notes = liftM vsep (zipWithM noteToMuse [1 ..] notes) -- | Return Muse representation of a note. noteToMuse :: PandocMonad m => Int -> [Block] - -> StateT WriterState m Doc + -> Muse m Doc noteToMuse num note = do contents <- blockListToMuse note let marker = "[" ++ show num ++ "] " @@ -377,7 +379,7 @@ fixOrEscape _ = False renderInlineList :: PandocMonad m => Bool -> [Inline] - -> StateT WriterState m Doc + -> Muse m Doc renderInlineList True [] = pure "" renderInlineList False [] = pure "" renderInlineList start (x:xs) = do r <- inlineToMuse x @@ -391,21 +393,21 @@ renderInlineList start (x:xs) = do r <- inlineToMuse x inlineListToMuse'' :: PandocMonad m => Bool -> [Inline] - -> StateT WriterState m Doc + -> Muse m Doc inlineListToMuse'' start lst = do lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) renderInlineList start lst' -inlineListToMuse' :: PandocMonad m => [Inline] -> StateT WriterState m Doc +inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc inlineListToMuse' = inlineListToMuse'' True -inlineListToMuse :: PandocMonad m => [Inline] -> StateT WriterState m Doc +inlineListToMuse :: PandocMonad m => [Inline] -> Muse m Doc inlineListToMuse = inlineListToMuse'' False -- | Convert Pandoc inline element to Muse. inlineToMuse :: PandocMonad m => Inline - -> StateT WriterState m Doc + -> Muse m Doc inlineToMuse (Str str) = return $ text $ conditionalEscapeString str inlineToMuse (Emph lst) = do contents <- inlineListToMuse lst -- cgit v1.2.3 From 7c268c492dbd768d1f7db83bc70f1db9dc2e838c Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Mar 2018 15:39:55 +0300 Subject: Muse writer: move options, stTopLevel and stInsideBlock to WriterEnv --- src/Text/Pandoc/Writers/Muse.hs | 63 +++++++++++++++++++++-------------------- 1 file changed, 33 insertions(+), 30 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 1257a3f06..74251a3bd 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -44,6 +44,7 @@ even though it is supported only in Emacs Muse. -} module Text.Pandoc.Writers.Muse (writeMuse) where import Prelude +import Control.Monad.Reader import Control.Monad.State.Strict import Data.Char (isSpace, isDigit, isAsciiUpper, isAsciiLower) import Data.Text (Text) @@ -61,15 +62,22 @@ import Text.Pandoc.Writers.Shared import qualified Data.Set as Set type Notes = [[Block]] + +type Muse m = ReaderT WriterEnv (StateT WriterState m) + +data WriterEnv = + WriterEnv { envOptions :: WriterOptions + , envTopLevel :: Bool + , envInsideBlock :: Bool + } + data WriterState = WriterState { stNotes :: Notes - , stOptions :: WriterOptions - , stTopLevel :: Bool - , stInsideBlock :: Bool , stIds :: Set.Set String } -type Muse = StateT WriterState +evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a +evalMuse document env st = evalStateT (runReaderT document env) st -- | Convert Pandoc to Muse. writeMuse :: PandocMonad m @@ -77,20 +85,21 @@ writeMuse :: PandocMonad m -> Pandoc -> m Text writeMuse opts document = - let st = WriterState { stNotes = [] - , stOptions = opts - , stTopLevel = True - , stInsideBlock = False - , stIds = Set.empty - } - in evalStateT (pandocToMuse document) st + evalMuse (pandocToMuse document) env st + where env = WriterEnv { envOptions = opts + , envTopLevel = True + , envInsideBlock = False + } + st = WriterState { stNotes = [] + , stIds = Set.empty + } -- | Return Muse representation of document. pandocToMuse :: PandocMonad m => Pandoc -> Muse m Text pandocToMuse (Pandoc meta blocks) = do - opts <- gets stOptions + opts <- asks envOptions let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing @@ -121,7 +130,7 @@ catWithBlankLines (b : bs) n = do catWithBlankLines _ _ = error "Expected at least one block" -- | Convert list of Pandoc block elements to Muse --- | without setting stTopLevel. +-- | without setting envTopLevel. flatBlockListToMuse :: PandocMonad m => [Block] -- ^ List of block elements -> Muse m Doc @@ -141,16 +150,10 @@ flatBlockListToMuse [] = return mempty blockListToMuse :: PandocMonad m => [Block] -- ^ List of block elements -> Muse m Doc -blockListToMuse blocks = do - oldState <- get - modify $ \s -> s { stTopLevel = not $ stInsideBlock s - , stInsideBlock = True - } - result <- flatBlockListToMuse blocks - modify $ \s -> s { stTopLevel = stTopLevel oldState - , stInsideBlock = stInsideBlock oldState - } - return result +blockListToMuse = + local (\env -> env { envTopLevel = not (envInsideBlock env) + , envInsideBlock = True + }) . flatBlockListToMuse -- | Convert Pandoc block element to Muse. blockToMuse :: PandocMonad m @@ -180,7 +183,7 @@ blockToMuse (OrderedList (start, style, _) items) = do (start, style, Period) contents <- zipWithM orderedListItemToMuse markers items -- ensure that sublists have preceding blank line - topLevel <- gets stTopLevel + topLevel <- asks envTopLevel return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where orderedListItemToMuse :: PandocMonad m => String -- ^ marker for list item @@ -192,7 +195,7 @@ blockToMuse (OrderedList (start, style, _) items) = do blockToMuse (BulletList items) = do contents <- mapM bulletListItemToMuse items -- ensure that sublists have preceding blank line - topLevel <- gets stTopLevel + topLevel <- asks envTopLevel return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where bulletListItemToMuse :: PandocMonad m => [Block] @@ -203,7 +206,7 @@ blockToMuse (BulletList items) = do blockToMuse (DefinitionList items) = do contents <- mapM definitionListItemToMuse items -- ensure that sublists have preceding blank line - topLevel <- gets stTopLevel + topLevel <- asks envTopLevel return $ cr $$ (if topLevel then nest 1 else id) (vcat contents) $$ blankline where definitionListItemToMuse :: PandocMonad m => ([Inline], [[Block]]) @@ -218,7 +221,7 @@ blockToMuse (DefinitionList items) = do -> Muse m Doc descriptionToMuse desc = hang 4 " :: " <$> blockListToMuse desc blockToMuse (Header level (ident,_,_) inlines) = do - opts <- gets stOptions + opts <- asks envOptions contents <- inlineListToMuse inlines ids <- gets stIds @@ -383,7 +386,7 @@ renderInlineList :: PandocMonad m renderInlineList True [] = pure "" renderInlineList False [] = pure "" renderInlineList start (x:xs) = do r <- inlineToMuse x - opts <- gets stOptions + opts <- asks envOptions lst' <- renderInlineList ((x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak) xs if start && fixOrEscape x then pure (text "" <> r <> lst') @@ -443,7 +446,7 @@ inlineToMuse (RawInline (Format f) str) = inlineToMuse LineBreak = return $ "
" <> cr inlineToMuse Space = return space inlineToMuse SoftBreak = do - wrapText <- gets $ writerWrapText . stOptions + wrapText <- asks $ writerWrapText . envOptions return $ if wrapText == WrapPreserve then cr else space inlineToMuse (Link _ txt (src, _)) = case txt of @@ -458,7 +461,7 @@ inlineToMuse (Link _ txt (src, _)) = inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) = inlineToMuse (Image attr alt (source,title)) inlineToMuse (Image attr inlines (source, title)) = do - opts <- gets stOptions + opts <- asks envOptions alt <- inlineListToMuse inlines let title' = if null title then if null inlines -- cgit v1.2.3 From d0a7dbd948351a6622a4d670bfbb8ef622e6278f Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 28 Mar 2018 15:49:50 +0300 Subject: Muse writer: implement Default for WriterState --- src/Text/Pandoc/Writers/Muse.hs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 74251a3bd..b03ce8f90 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -47,6 +47,7 @@ import Prelude import Control.Monad.Reader import Control.Monad.State.Strict import Data.Char (isSpace, isDigit, isAsciiUpper, isAsciiLower) +import Data.Default import Data.Text (Text) import Data.List (intersperse, transpose, isInfixOf) import System.FilePath (takeExtension) @@ -76,6 +77,11 @@ data WriterState = , stIds :: Set.Set String } +instance Default WriterState + where def = WriterState { stNotes = [] + , stIds = Set.empty + } + evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a evalMuse document env st = evalStateT (runReaderT document env) st @@ -85,14 +91,11 @@ writeMuse :: PandocMonad m -> Pandoc -> m Text writeMuse opts document = - evalMuse (pandocToMuse document) env st - where env = WriterEnv { envOptions = opts - , envTopLevel = True - , envInsideBlock = False - } - st = WriterState { stNotes = [] - , stIds = Set.empty - } + evalMuse (pandocToMuse document) env def + where env = WriterEnv { envOptions = opts + , envTopLevel = True + , envInsideBlock = False + } -- | Return Muse representation of document. pandocToMuse :: PandocMonad m -- cgit v1.2.3 From bdb84246970151dd9bbb7a0713e36707488f9d97 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sat, 31 Mar 2018 22:44:24 +0300 Subject: Muse writer: do not escape list markers unless preceded by space --- src/Text/Pandoc/Writers/Muse.hs | 54 ++++++++++++++++++++++++++--------------- test/Tests/Writers/Muse.hs | 1 + test/writer.muse | 4 +-- 3 files changed, 37 insertions(+), 22 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index b03ce8f90..44224122e 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -70,6 +70,8 @@ data WriterEnv = WriterEnv { envOptions :: WriterOptions , envTopLevel :: Bool , envInsideBlock :: Bool + , envInlineStart :: Bool + , envAfterSpace :: Bool } data WriterState = @@ -95,6 +97,8 @@ writeMuse opts document = where env = WriterEnv { envOptions = opts , envTopLevel = True , envInsideBlock = False + , envInlineStart = True + , envAfterSpace = True } -- | Return Muse representation of document. @@ -371,29 +375,36 @@ urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs urlEscapeBrackets [] = [] -fixOrEscape :: Inline -> Bool -fixOrEscape (Str "-") = True -- TODO: " - " should be escaped too -fixOrEscape (Str ";") = True -fixOrEscape (Str s) = startsWithMarker isDigit s || - startsWithMarker isAsciiLower s || - startsWithMarker isAsciiUpper s -fixOrEscape Space = True -fixOrEscape SoftBreak = True -fixOrEscape _ = False +fixOrEscape :: Bool -> Inline -> Bool +fixOrEscape sp (Str "-") = sp +fixOrEscape sp (Str ";") = not sp +fixOrEscape sp (Str s) = sp && (startsWithMarker isDigit s || + startsWithMarker isAsciiLower s || + startsWithMarker isAsciiUpper s) +fixOrEscape _ Space = True +fixOrEscape _ SoftBreak = True +fixOrEscape _ _ = False -- | Convert list of Pandoc inline elements to Muse renderInlineList :: PandocMonad m - => Bool - -> [Inline] + => [Inline] -> Muse m Doc -renderInlineList True [] = pure "" -renderInlineList False [] = pure "" -renderInlineList start (x:xs) = do r <- inlineToMuse x - opts <- asks envOptions - lst' <- renderInlineList ((x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak) xs - if start && fixOrEscape x - then pure (text "" <> r <> lst') - else pure (r <> lst') +renderInlineList [] = do + start <- asks envInlineStart + pure $ if start then "" else "" +renderInlineList (x:xs) = do + start <- asks envInlineStart + afterSpace <- asks envAfterSpace + topLevel <- asks envTopLevel + r <- inlineToMuse x + opts <- asks envOptions + let isNewline = (x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak + lst' <- local (\env -> env { envInlineStart = isNewline + , envAfterSpace = (x == Space || (not topLevel && isNewline)) + }) $ renderInlineList xs + if start && fixOrEscape afterSpace x + then pure (text "" <> r <> lst') + else pure (r <> lst') -- | Normalize and convert list of Pandoc inline elements to Muse. inlineListToMuse'' :: PandocMonad m @@ -402,7 +413,10 @@ inlineListToMuse'' :: PandocMonad m -> Muse m Doc inlineListToMuse'' start lst = do lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) - renderInlineList start lst' + topLevel <- asks envTopLevel + local (\env -> env { envInlineStart = start + , envAfterSpace = start && not topLevel + }) $ renderInlineList lst' inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc inlineListToMuse' = inlineListToMuse'' True diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index c1bec1ba2..88d2db8cf 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -324,6 +324,7 @@ tests = [ testGroup "block elements" , "escape ; to avoid accidental comments" =: text "; foo" =?> "; foo" , "escape ; after softbreak" =: text "foo" <> softbreak <> text "; bar" =?> "foo\n; bar" , "escape ; after linebreak" =: text "foo" <> linebreak <> text "; bar" =?> "foo
\n; bar" + , "do not escape ; inside paragraph" =: text "foo ; bar" =?> "foo ; bar" ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" diff --git a/test/writer.muse b/test/writer.muse index abb6b63fe..c534b63b3 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -42,7 +42,7 @@ item. Here’s one with a bullet. * criminey. There should be a hard line break
-here. +here. ---- @@ -245,7 +245,7 @@ Should not be a list item: M.A. 2007 -B. Williams +B. Williams ---- -- cgit v1.2.3 From aca4137c4094ec921276bf50278dfc58db5634a3 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 14 Mar 2018 12:23:51 +0300 Subject: Muse writer: only escape brackets when necessary It includes cases when they can be mistaken for footnotes and links, as well as inside link description. --- src/Text/Pandoc/Writers/Muse.hs | 45 +++++++++++++++++++++++++++++++---------- test/Tests/Writers/Muse.hs | 3 +++ test/writer.muse | 12 +++++------ 3 files changed, 43 insertions(+), 17 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 44224122e..eaae43604 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -67,11 +67,12 @@ type Notes = [[Block]] type Muse m = ReaderT WriterEnv (StateT WriterState m) data WriterEnv = - WriterEnv { envOptions :: WriterOptions - , envTopLevel :: Bool + WriterEnv { envOptions :: WriterOptions + , envTopLevel :: Bool , envInsideBlock :: Bool , envInlineStart :: Bool - , envAfterSpace :: Bool + , envInsideLinkDescription :: Bool -- Escape ] if True + , envAfterSpace :: Bool } data WriterState = @@ -98,6 +99,7 @@ writeMuse opts document = , envTopLevel = True , envInsideBlock = False , envInlineStart = True + , envInsideLinkDescription = False , envAfterSpace = True } @@ -304,12 +306,31 @@ startsWithMarker f (x:xs) = startsWithMarker _ [] = False -- | Escape special characters for Muse if needed. -conditionalEscapeString :: String -> String -conditionalEscapeString s = - if any (`elem` ("#*<=>[]|" :: String)) s || +containsFootnotes :: String -> Bool +containsFootnotes st = + p st + where p ('[':xs) = q xs || p xs + p (_:xs) = p xs + p "" = False + q (x:xs) + | (x `elem` ("123456789"::String)) = r xs || p xs + | otherwise = p xs + q [] = False + r ('0':xs) = r xs || p xs + r (xs) = s xs || q xs || p xs + s (']':_) = True + s (_:xs) = p xs + s [] = False + +conditionalEscapeString :: Bool -> String -> String +conditionalEscapeString isInsideLinkDescription s = + if any (`elem` ("#*<=>|" :: String)) s || "::" `isInfixOf` s || "----" `isInfixOf` s || - "~~" `isInfixOf` s + "~~" `isInfixOf` s || + "[[" `isInfixOf` s || + ("]" `isInfixOf` s && isInsideLinkDescription) || + containsFootnotes s then escapeString s else s @@ -428,7 +449,9 @@ inlineListToMuse = inlineListToMuse'' False inlineToMuse :: PandocMonad m => Inline -> Muse m Doc -inlineToMuse (Str str) = return $ text $ conditionalEscapeString str +inlineToMuse (Str str) = do + insideLink <- asks envInsideLinkDescription + return $ text $ conditionalEscapeString insideLink str inlineToMuse (Emph lst) = do contents <- inlineListToMuse lst return $ "" <> contents <> "" @@ -469,7 +492,7 @@ inlineToMuse (Link _ txt (src, _)) = case txt of [Str x] | escapeURI x == src -> return $ "[[" <> text (escapeLink x) <> "]]" - _ -> do contents <- inlineListToMuse txt + _ -> do contents <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse txt return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]" where escapeLink lnk = if isImageUrl lnk then "URL:" ++ urlEscapeBrackets lnk else urlEscapeBrackets lnk -- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el @@ -479,7 +502,7 @@ inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) = inlineToMuse (Image attr alt (source,title)) inlineToMuse (Image attr inlines (source, title)) = do opts <- asks envOptions - alt <- inlineListToMuse inlines + alt <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse inlines let title' = if null title then if null inlines then "" @@ -489,7 +512,7 @@ inlineToMuse (Image attr inlines (source, title)) = do Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" - where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString s + where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString True s inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 88d2db8cf..eca7ed736 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -301,8 +301,11 @@ tests = [ testGroup "block elements" [ testGroup "string" [ "string" =: str "foo" =?> "foo" , "escape footnote" =: str "[1]" =?> "[1]" + , "do not escape brackets" =: str "[12ab]" =?> "[12ab]" , "escape verbatim close tag" =: str "foobar" =?> "foo</verbatim>bar" + , "escape link-like text" =: str "[[https://www.example.org]]" + =?> "[[https://www.example.org]]" , "escape pipe to avoid accidental tables" =: str "foo | bar" =?> "foo | bar" , "escape hash to avoid accidental anchors" =: text "#foo bar" diff --git a/test/writer.muse b/test/writer.muse index c534b63b3..83a53a1ab 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -576,9 +576,9 @@ Left brace: { Right brace: } -Left bracket: [ +Left bracket: [ -Right bracket: ] +Right bracket: ] Left paren: ( @@ -634,7 +634,7 @@ Indented [[/url][twice]]. Indented [[/url][thrice]]. -This should [not][] be a link. +This should [not][] be a link. [not]: /url @@ -690,8 +690,8 @@ Here is a movie [[movie.jpg][movie]] icon. * Footnotes Here is a footnote reference,[1] and another.[2] This should not be a -footnote reference, because it contains a space.[^my -note] Here is an inline note.[3] +footnote reference, because it contains a space.[^my note] Here is an inline +note.[3] Notes can go in quotes.[4] @@ -718,7 +718,7 @@ This paragraph should not be part of the note, as it is not indented. [3] This is easier to type. Inline notes may contain [[http://google.com][links]] and ] verbatim characters, as - well as [bracketed text]. + well as [bracketed text]. [4] In quote. -- cgit v1.2.3 From ca78d93b408c660ee1ab753e165d07acd864b5a7 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 2 Apr 2018 15:55:04 +0300 Subject: Muse writer: place header IDs before header See https://github.com/melmothx/text-amuse/issues/39 --- src/Text/Pandoc/Readers/Muse.hs | 4 ++-- src/Text/Pandoc/Writers/Muse.hs | 3 +-- test/Tests/Readers/Muse.hs | 3 ++- test/Tests/Writers/Muse.hs | 4 ++-- 4 files changed, 7 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index b43a53d60..9e2ec310d 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -363,12 +363,12 @@ separator = try $ do header :: PandocMonad m => MuseParser m (F Blocks) header = try $ do + anchorId <- option "" $ try (parseAnchor <* manyTill spaceChar eol) getPosition >>= \pos -> guard (sourceColumn pos == 1) level <- fmap length $ many1 $ char '*' guard $ level <= 5 spaceChar content <- trimInlinesF . mconcat <$> manyTill inline eol - anchorId <- option "" parseAnchor attr <- registerHeader (anchorId, [], []) (runF content def) return $ B.headerWith attr level <$> content @@ -781,12 +781,12 @@ parseAnchor = try $ do char '#' first <- letter rest <- many (letter <|> digit) - skipMany spaceChar <|> void newline return $ first:rest anchor :: PandocMonad m => MuseParser m (F Inlines) anchor = try $ do anchorId <- parseAnchor + skipMany spaceChar <|> void newline return $ return $ B.spanWith (anchorId, [], []) mempty footnote :: PandocMonad m => MuseParser m (F Inlines) diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index eaae43604..a5cb71d8c 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -241,8 +241,7 @@ blockToMuse (Header level (ident,_,_) inlines) = do then empty else "#" <> text ident <> cr let header' = text $ replicate level '*' - return $ blankline <> nowrap (header' <> space <> contents) - $$ attr' <> blankline + return $ blankline <> attr' $$ nowrap (header' <> space <> contents) <> blankline -- https://www.gnu.org/software/emacs-muse/manual/muse.html#Horizontal-Rules-and-Anchors blockToMuse HorizontalRule = return $ blankline $$ "----" $$ blankline blockToMuse (Table caption _ _ headers rows) = do diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index ca63a6579..56ad9f249 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -533,8 +533,9 @@ tests = ] =?> blockQuote (para "* Hi") , "Headers consume anchors" =: - T.unlines [ "** Foo" + T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#bar" + , "** Foo" ] =?> headerWith ("bar",[],[]) 2 "Foo" , "Headers don't consume anchors separated with a blankline" =: diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index eca7ed736..33ba2b1fb 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -254,8 +254,8 @@ tests = [ testGroup "block elements" ] , "heading with ID" =: headerWith ("bar", [], []) 2 (text "Foo") =?> - unlines [ "** Foo" - , "#bar" + unlines [ "#bar" + , "** Foo" ] ] , "horizontal rule" =: horizontalRule =?> "----" -- cgit v1.2.3 From dfbae03810b168dc8af3127318918fb13ecbdc55 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 2 Apr 2018 16:20:35 +0300 Subject: hlint Muse writer --- src/Text/Pandoc/Writers/Muse.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index a5cb71d8c..90deee11b 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -119,7 +119,7 @@ pandocToMuse (Pandoc meta blocks) = do (fmap render' . inlineListToMuse) meta body <- blockListToMuse blocks - notes <- liftM (reverse . stNotes) get >>= notesToMuse + notes <- fmap (reverse . stNotes) get >>= notesToMuse let main = render colwidth $ body $+$ notes let context = defField "body" main metadata case writerTemplate opts of @@ -222,7 +222,7 @@ blockToMuse (DefinitionList items) = do -> Muse m Doc definitionListItemToMuse (label, defs) = do label' <- inlineListToMuse' label - contents <- liftM vcat $ mapM descriptionToMuse defs + contents <- vcat <$> mapM descriptionToMuse defs let ind = offset label' return $ hang ind label' contents descriptionToMuse :: PandocMonad m @@ -275,7 +275,7 @@ blockToMuse Null = return empty notesToMuse :: PandocMonad m => Notes -> Muse m Doc -notesToMuse notes = liftM vsep (zipWithM noteToMuse [1 ..] notes) +notesToMuse notes = vsep <$> (zipWithM noteToMuse [1 ..] notes) -- | Return Muse representation of a note. noteToMuse :: PandocMonad m @@ -312,11 +312,11 @@ containsFootnotes st = p (_:xs) = p xs p "" = False q (x:xs) - | (x `elem` ("123456789"::String)) = r xs || p xs + | x `elem` ("123456789"::String) = r xs || p xs | otherwise = p xs q [] = False r ('0':xs) = r xs || p xs - r (xs) = s xs || q xs || p xs + r xs = s xs || q xs || p xs s (']':_) = True s (_:xs) = p xs s [] = False @@ -420,7 +420,7 @@ renderInlineList (x:xs) = do opts <- asks envOptions let isNewline = (x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak lst' <- local (\env -> env { envInlineStart = isNewline - , envAfterSpace = (x == Space || (not topLevel && isNewline)) + , envAfterSpace = x == Space || (not topLevel && isNewline) }) $ renderInlineList xs if start && fixOrEscape afterSpace x then pure (text "" <> r <> lst') -- cgit v1.2.3 From 8837af879add64e4c0e04505e0a469620d6404c1 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 3 Apr 2018 15:39:14 +0300 Subject: Muse writer: rewrite noteToMuse without do --- src/Text/Pandoc/Writers/Muse.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 90deee11b..aae6b3d9d 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -282,10 +282,10 @@ noteToMuse :: PandocMonad m => Int -> [Block] -> Muse m Doc -noteToMuse num note = do - contents <- blockListToMuse note - let marker = "[" ++ show num ++ "] " - return $ hang (length marker) (text marker) contents +noteToMuse num note = + hang (length marker) (text marker) <$> blockListToMuse note + where + marker = "[" ++ show num ++ "] " -- | Escape special characters for Muse. escapeString :: String -> String -- cgit v1.2.3 From 16104881b34596b39e41d4fd47f3e3af68e575ac Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 5 Apr 2018 13:12:17 +0300 Subject: Muse writer: simplify escaping in inlineToMuse Image{} --- src/Text/Pandoc/Writers/Muse.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index aae6b3d9d..4986aa8a6 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -506,12 +506,11 @@ inlineToMuse (Image attr inlines (source, title)) = do then if null inlines then "" else "[" <> alt <> "]" - else "[" <> text (escape title) <> "]" + else "[" <> text (conditionalEscapeString True title) <> "]" let width = case dimension Width attr of Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" - where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString True s inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes -- cgit v1.2.3 From 87dda2109d01098dcf41c01559d3e91e2627cd10 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 5 Apr 2018 19:48:39 +0300 Subject: Muse writer: escape horizontal rule only if at the beginning of the line --- src/Text/Pandoc/Writers/Muse.hs | 11 ++++++++--- test/Tests/Writers/Muse.hs | 4 +++- 2 files changed, 11 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 4986aa8a6..e9cf6d433 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -325,7 +325,6 @@ conditionalEscapeString :: Bool -> String -> String conditionalEscapeString isInsideLinkDescription s = if any (`elem` ("#*<=>|" :: String)) s || "::" `isInfixOf` s || - "----" `isInfixOf` s || "~~" `isInfixOf` s || "[[" `isInfixOf` s || ("]" `isInfixOf` s && isInsideLinkDescription) || @@ -395,12 +394,18 @@ urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs urlEscapeBrackets [] = [] +isHorizontalRule :: String -> Bool +isHorizontalRule s = + ((length xs) >= 4) && null ys + where (xs, ys) = span (== '-') s + fixOrEscape :: Bool -> Inline -> Bool fixOrEscape sp (Str "-") = sp fixOrEscape sp (Str ";") = not sp -fixOrEscape sp (Str s) = sp && (startsWithMarker isDigit s || +fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s || startsWithMarker isAsciiLower s || - startsWithMarker isAsciiUpper s) + startsWithMarker isAsciiUpper s)) + || isHorizontalRule s fixOrEscape _ Space = True fixOrEscape _ SoftBreak = True fixOrEscape _ _ = False diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 33ba2b1fb..115a00f83 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -259,7 +259,9 @@ tests = [ testGroup "block elements" ] ] , "horizontal rule" =: horizontalRule =?> "----" - , "escape horizontal rule" =: para (text "----") =?> "----" + , "escape horizontal rule" =: para (text "----") =?> "----" + , "escape long horizontal rule" =: para (text "----------") =?> "----------" + , "don't escape horizontal inside paragraph" =: para (text "foo ---- bar") =?> "foo ---- bar" , "escape nonbreaking space" =: para (text "~~") =?> "~~" , testGroup "tables" [ "table without header" =: -- cgit v1.2.3 From 44093930a8048331389534cc2b6f81400bb93c72 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 9 Apr 2018 04:09:18 +0300 Subject: Muse writer: correctly output empty headings --- src/Text/Pandoc/Writers/Muse.hs | 3 +-- test/Tests/Writers/Muse.hs | 1 + 2 files changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index e9cf6d433..2ea7f04e2 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -231,8 +231,7 @@ blockToMuse (DefinitionList items) = do descriptionToMuse desc = hang 4 " :: " <$> blockListToMuse desc blockToMuse (Header level (ident,_,_) inlines) = do opts <- asks envOptions - contents <- inlineListToMuse inlines - + contents <- inlineListToMuse' inlines ids <- gets stIds let autoId = uniqueIdent inlines ids modify $ \st -> st{ stIds = Set.insert autoId ids } diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 96f506cd5..0526b2854 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -257,6 +257,7 @@ tests = [ testGroup "block elements" unlines [ "#bar" , "** Foo" ] + , "empty heading" =: header 4 (mempty) =?> "**** " ] , "horizontal rule" =: horizontalRule =?> "----" , "escape horizontal rule" =: para (text "----") =?> "----" -- cgit v1.2.3 From 79b67dec7812cbd969a4fb53275cfeeaf2b54913 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 9 Apr 2018 03:15:46 +0300 Subject: Muse writer: fix Haddock comment --- src/Text/Pandoc/Writers/Muse.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 2ea7f04e2..0f11bb7b5 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -71,7 +71,7 @@ data WriterEnv = , envTopLevel :: Bool , envInsideBlock :: Bool , envInlineStart :: Bool - , envInsideLinkDescription :: Bool -- Escape ] if True + , envInsideLinkDescription :: Bool -- ^ Escape ] if True , envAfterSpace :: Bool } -- cgit v1.2.3 From 52803e2960c3520f8b2159f9076cb454c03988f8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 9 Apr 2018 03:16:55 +0300 Subject: Muse writer: don't break headers, line blocks and tables with line breaks --- src/Text/Pandoc/Writers/Muse.hs | 15 ++++++++++----- test/Tests/Writers/Muse.hs | 2 ++ 2 files changed, 12 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 0f11bb7b5..0cfc2b8c4 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -73,6 +73,7 @@ data WriterEnv = , envInlineStart :: Bool , envInsideLinkDescription :: Bool -- ^ Escape ] if True , envAfterSpace :: Bool + , envOneLine :: Bool -- ^ True if newlines are not allowed } data WriterState = @@ -101,6 +102,7 @@ writeMuse opts document = , envInlineStart = True , envInsideLinkDescription = False , envAfterSpace = True + , envOneLine = False } -- | Return Muse representation of document. @@ -173,7 +175,7 @@ blockToMuse (Para inlines) = do contents <- inlineListToMuse' inlines return $ contents <> blankline blockToMuse (LineBlock lns) = do - lns' <- mapM inlineListToMuse lns + lns' <- local (\env -> env { envOneLine = True }) $ mapM inlineListToMuse lns return $ nowrap $ vcat (map (text "> " <>) lns') <> blankline blockToMuse (CodeBlock (_,_,_) str) = return $ "" $$ text str $$ "" $$ blankline @@ -221,7 +223,7 @@ blockToMuse (DefinitionList items) = do => ([Inline], [[Block]]) -> Muse m Doc definitionListItemToMuse (label, defs) = do - label' <- inlineListToMuse' label + label' <- local (\env -> env { envOneLine = True }) $ inlineListToMuse' label contents <- vcat <$> mapM descriptionToMuse defs let ind = offset label' return $ hang ind label' contents @@ -231,7 +233,7 @@ blockToMuse (DefinitionList items) = do descriptionToMuse desc = hang 4 " :: " <$> blockListToMuse desc blockToMuse (Header level (ident,_,_) inlines) = do opts <- asks envOptions - contents <- inlineListToMuse' inlines + contents <- local (\env -> env { envOneLine = True }) $ inlineListToMuse' inlines ids <- gets stIds let autoId = uniqueIdent inlines ids modify $ \st -> st{ stIds = Set.insert autoId ids } @@ -486,11 +488,14 @@ inlineToMuse Math{} = fail "Math should be expanded before normalization" inlineToMuse (RawInline (Format f) str) = return $ " text f <> "\">" <> text str <> "" -inlineToMuse LineBreak = return $ "
" <> cr +inlineToMuse LineBreak = do + oneline <- asks envOneLine + return $ if oneline then "
" else "
" <> cr inlineToMuse Space = return space inlineToMuse SoftBreak = do + oneline <- asks envOneLine wrapText <- asks $ writerWrapText . envOptions - return $ if wrapText == WrapPreserve then cr else space + return $ if not oneline && wrapText == WrapPreserve then cr else space inlineToMuse (Link _ txt (src, _)) = case txt of [Str x] | escapeURI x == src -> diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 0526b2854..5d84150e1 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -360,6 +360,8 @@ tests = [ testGroup "block elements" "remove soft break" $ text "a" <> softbreak <> text "b" =?> "a b" , "line break" =: text "a" <> linebreak <> text "b" =?> "a
\nb" + , "no newline after line break in header" =: header 1 (text "a" <> linebreak <> text "b") =?> "* a
b" + , "no softbreak in header" =: header 1 (text "a" <> softbreak <> text "b") =?> "* a b" ] , testGroup "math" [ "inline math" =: math "2^3" =?> "23" -- cgit v1.2.3 From 782ab73aa350ca323b0b7786770e37d1a932f9a8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Tue, 10 Apr 2018 23:38:30 +0300 Subject: Muse writer: escape > less often > should be escaped only when it can start verse, i.e., at the beginning of the line. --- src/Text/Pandoc/Writers/Muse.hs | 3 ++- test/Tests/Writers/Muse.hs | 1 + test/writer.muse | 6 +++--- 3 files changed, 6 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 0cfc2b8c4..127a4f149 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -324,7 +324,7 @@ containsFootnotes st = conditionalEscapeString :: Bool -> String -> String conditionalEscapeString isInsideLinkDescription s = - if any (`elem` ("#*<=>|" :: String)) s || + if any (`elem` ("#*<=|" :: String)) s || "::" `isInfixOf` s || "~~" `isInfixOf` s || "[[" `isInfixOf` s || @@ -403,6 +403,7 @@ isHorizontalRule s = fixOrEscape :: Bool -> Inline -> Bool fixOrEscape sp (Str "-") = sp fixOrEscape sp (Str ";") = not sp +fixOrEscape _ (Str ">") = True fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s || startsWithMarker isAsciiLower s || startsWithMarker isAsciiUpper s)) diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 5d84150e1..41c846b1b 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -264,6 +264,7 @@ tests = [ testGroup "block elements" , "escape long horizontal rule" =: para (text "----------") =?> "----------" , "don't escape horizontal inside paragraph" =: para (text "foo ---- bar") =?> "foo ---- bar" , "escape nonbreaking space" =: para (text "~~") =?> "~~" + , "escape > in the beginning of line" =: para (text "> foo bar") =?> "> foo bar" , testGroup "tables" [ "table without header" =: let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] diff --git a/test/writer.muse b/test/writer.muse index 83a53a1ab..9492a5517 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -79,7 +79,7 @@ nested
-This should not be a block quote: 2 > 1. +This should not be a block quote: 2 > 1. And a following paragraph. @@ -562,7 +562,7 @@ This & that. 4 < 5. -6 > 5. +6 > 5. Backslash: \ @@ -584,7 +584,7 @@ Left paren: ( Right paren: ) -Greater-than: > +Greater-than: > Hash: # -- cgit v1.2.3 From 17767bd29d54883364d4d9bdee417973ac0a10ac Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 15 Apr 2018 16:07:43 +0300 Subject: Muse writer: escape strings starting with space --- src/Text/Pandoc/Writers/Muse.hs | 6 +++++- test/Tests/Writers/Muse.hs | 9 +++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 127a4f149..4e7ce377a 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -400,6 +400,10 @@ isHorizontalRule s = ((length xs) >= 4) && null ys where (xs, ys) = span (== '-') s +startsWithSpace :: String -> Bool +startsWithSpace (x:_) = isSpace x +startsWithSpace [] = False + fixOrEscape :: Bool -> Inline -> Bool fixOrEscape sp (Str "-") = sp fixOrEscape sp (Str ";") = not sp @@ -407,7 +411,7 @@ fixOrEscape _ (Str ">") = True fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s || startsWithMarker isAsciiLower s || startsWithMarker isAsciiUpper s)) - || isHorizontalRule s + || isHorizontalRule s || startsWithSpace s fixOrEscape _ Space = True fixOrEscape _ SoftBreak = True fixOrEscape _ _ = False diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 41c846b1b..44fdd5b7e 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -112,6 +112,15 @@ tests = [ testGroup "block elements" , " :: second description" , " :: third description" ] + , "definition list terms starting with space" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (space <> str "foo", [plain $ text "second description"]) + , (str " > bar", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " foo :: second description" + , " > bar :: third description" + ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" -- cgit v1.2.3 From f39931fd6c86a4bf7a651f9e2f5667bfad99bcca Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 11:40:18 +0300 Subject: Muse writer: escape definition list terms starting with list markers --- src/Text/Pandoc/Writers/Muse.hs | 13 +++++++------ test/Tests/Writers/Muse.hs | 9 +++++++++ 2 files changed, 16 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 4e7ce377a..d1e407026 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -101,7 +101,7 @@ writeMuse opts document = , envInsideBlock = False , envInlineStart = True , envInsideLinkDescription = False - , envAfterSpace = True + , envAfterSpace = False , envOneLine = False } @@ -223,7 +223,7 @@ blockToMuse (DefinitionList items) = do => ([Inline], [[Block]]) -> Muse m Doc definitionListItemToMuse (label, defs) = do - label' <- local (\env -> env { envOneLine = True }) $ inlineListToMuse' label + label' <- local (\env -> env { envOneLine = True, envAfterSpace = True }) $ inlineListToMuse' label contents <- vcat <$> mapM descriptionToMuse defs let ind = offset label' return $ hang ind label' contents @@ -439,14 +439,15 @@ renderInlineList (x:xs) = do -- | Normalize and convert list of Pandoc inline elements to Muse. inlineListToMuse'' :: PandocMonad m - => Bool - -> [Inline] - -> Muse m Doc + => Bool + -> [Inline] + -> Muse m Doc inlineListToMuse'' start lst = do lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) topLevel <- asks envTopLevel + afterSpace <- asks envAfterSpace local (\env -> env { envInlineStart = start - , envAfterSpace = start && not topLevel + , envAfterSpace = afterSpace || (start && not topLevel) }) $ renderInlineList lst' inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 44fdd5b7e..ff66d1d65 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -121,6 +121,15 @@ tests = [ testGroup "block elements" , " foo :: second description" , " > bar :: third description" ] + , "definition list terms starting with list markers" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (str "-", [plain $ text "second description"]) + , (str "1.", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " - :: second description" + , " 1. :: third description" + ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" -- cgit v1.2.3 From 46cc1e73b63c7046d7311cb4551bcc1794af41a8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 15:36:30 +0300 Subject: Muse writer: simplify isHorizontalRule --- src/Text/Pandoc/Writers/Muse.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index d1e407026..17ca727c1 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -396,9 +396,7 @@ urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs urlEscapeBrackets [] = [] isHorizontalRule :: String -> Bool -isHorizontalRule s = - ((length xs) >= 4) && null ys - where (xs, ys) = span (== '-') s +isHorizontalRule s = length s >= 4 && all (== '-') s startsWithSpace :: String -> Bool startsWithSpace (x:_) = isSpace x -- cgit v1.2.3 From 04478cf0e2930b00d962bcb55b28bc26889fd049 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 16:03:49 +0300 Subject: hlint Muse writer --- src/Text/Pandoc/Writers/Muse.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 17ca727c1..6ed6ed1ca 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -87,7 +87,7 @@ instance Default WriterState } evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a -evalMuse document env st = evalStateT (runReaderT document env) st +evalMuse document env = evalStateT $ runReaderT document env -- | Convert Pandoc to Muse. writeMuse :: PandocMonad m @@ -276,7 +276,7 @@ blockToMuse Null = return empty notesToMuse :: PandocMonad m => Notes -> Muse m Doc -notesToMuse notes = vsep <$> (zipWithM noteToMuse [1 ..] notes) +notesToMuse notes = vsep <$> zipWithM noteToMuse [1 ..] notes -- | Return Muse representation of a note. noteToMuse :: PandocMonad m @@ -307,8 +307,7 @@ startsWithMarker _ [] = False -- | Escape special characters for Muse if needed. containsFootnotes :: String -> Bool -containsFootnotes st = - p st +containsFootnotes = p where p ('[':xs) = q xs || p xs p (_:xs) = p xs p "" = False -- cgit v1.2.3 From 58799234227200b480b21a8f6611bdf3b6e2528a Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 7 May 2018 14:54:20 +0300 Subject: Muse writer: add support for left-align and right-align classes Address issue #4542 --- src/Text/Pandoc/Writers/Muse.hs | 10 ++++++++-- test/Tests/Writers/Muse.hs | 6 ++++++ 2 files changed, 14 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/Muse.hs') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 6ed6ed1ca..3681fcc0d 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -511,7 +511,7 @@ inlineToMuse (Link _ txt (src, _)) = isImageUrl = (`elem` imageExtensions) . takeExtension inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) = inlineToMuse (Image attr alt (source,title)) -inlineToMuse (Image attr inlines (source, title)) = do +inlineToMuse (Image attr@(_, classes, _) inlines (source, title)) = do opts <- asks envOptions alt <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse inlines let title' = if null title @@ -522,7 +522,13 @@ inlineToMuse (Image attr inlines (source, title)) = do let width = case dimension Width attr of Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" - return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" + let leftalign = if "align-left" `elem` classes + then " l" + else "" + let rightalign = if "align-right" `elem` classes + then " r" + else "" + return $ "[[" <> text (urlEscapeBrackets source ++ width ++ leftalign ++ rightalign) <> "]" <> title' <> "]" inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index ff66d1d65..50c0e78eb 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -425,6 +425,12 @@ tests = [ testGroup "block elements" , "image with width" =: imageWith ("", [], [("width", "60%")]) "image.png" "Image" (str "") =?> "[[image.png 60][Image]]" + , "left-aligned image with width" =: + imageWith ("", ["align-left"], [("width", "60%")]) "image.png" "Image" (str "") =?> + "[[image.png 60 l][Image]]" + , "right-aligned image with width" =: + imageWith ("", ["align-right"], [("width", "60%")]) "image.png" "Image" (str "") =?> + "[[image.png 60 r][Image]]" , "escape brackets in image title" =: image "image.png" "Foo]bar" (str "") =?> "[[image.png][Foo]bar]]" , "note" =: note (plain (text "Foo")) =?> unlines [ "[1]" -- cgit v1.2.3