diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Main.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 7 |
4 files changed, 8 insertions, 8 deletions
diff --git a/src/Main.hs b/src/Main.hs index dc5a9fde1..d279d5d3d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -19,7 +19,7 @@ import Text.Pandoc.Shared import System ( exitWith, getArgs, getProgName ) import System.Exit import System.Console.GetOpt -import IO ( stdout, stderr, hPutStrLn ) +import System.IO import Data.Maybe ( fromMaybe ) import Data.List ( isPrefixOf ) import Char ( toLower ) @@ -286,7 +286,7 @@ main = do writerIncludeBefore = includeBefore, writerIncludeAfter = includeAfter } - (readSources sources) >>= (putStrLn . encodeUTF8 . (writer writerOptions) . + (readSources sources) >>= (putStr . encodeUTF8 . (writer writerOptions) . (reader startParserState) . filter . decodeUTF8 . (joinWithSep "\n")) diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 07afba00e..b2686d941 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -140,7 +140,7 @@ prettyBlock block = show block -- | Prettyprint Pandoc document. prettyPandoc :: Pandoc -> String -prettyPandoc (Pandoc meta blocks) = "Pandoc " ++ "(" ++ (show meta) ++ ")\n" ++ (prettyBlockList 0 blocks) +prettyPandoc (Pandoc meta blocks) = "Pandoc " ++ "(" ++ (show meta) ++ ")\n" ++ (prettyBlockList 0 blocks) ++ "\n" -- | Convert tabs to spaces (with adjustable tab stop). tabsToSpaces :: Int -- ^ Tabstop diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 4ca131455..e7c167eb3 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -11,8 +11,7 @@ import Text.PrettyPrint.HughesPJ hiding ( Str ) writeMarkdown :: WriterOptions -> Pandoc -> String writeMarkdown options (Pandoc meta blocks) = let body = text (writerIncludeBefore options) <> - vcat (map (blockToMarkdown (writerTabStop options)) (formatKeys blocks)) $$ - text (writerIncludeAfter options) in + vcat (map (blockToMarkdown (writerTabStop options)) (formatKeys blocks)) $$ text (writerIncludeAfter options) in let head = if (writerStandalone options) then ((metaToMarkdown meta) $$ text (writerHeader options)) else diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 7d08d152d..cc2bc6499 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -16,14 +16,15 @@ writeRST options (Pandoc meta blocks) = (metaToRST meta) $$ text (writerHeader options) else empty in - let refs' = nubBy (\x y -> (render x) == (render y)) refs in -- remove duplicate keys + -- remove duplicate keys + let refs' = nubBy (\x y -> (render x) == (render y)) refs in let body = text (writerIncludeBefore options) <> vcat main $$ text (writerIncludeAfter options) in - render $ top <> body $$ vcat refs' + render $ top <> body $$ vcat refs' $$ text "\n" -- | Escape special RST characters. escapeString :: String -> String -escapeString = backslashEscape "`\\|*_" +escapeString = backslashEscape "`\\|*_" -- | Convert list of inline elements into one 'Doc' of wrapped text and another -- containing references. |