From aab574f9ef78792e53bfc55aa58635ecaf8b2a90 Mon Sep 17 00:00:00 2001 From: fiddlosopher Date: Thu, 31 Dec 2009 16:48:21 +0000 Subject: Use System.IO.UTF8 only if ghc < 6.12. GHC >= 6.12 (base >= 4.2) uses iconv to convert to unicode Strings. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1748 788f1e2b-df1e-0410-8736-df70ead52e1b --- src/Text/Pandoc.hs | 6 ++++-- src/Text/Pandoc/Shared.hs | 7 ++++++- src/hsmarkdown.hs | 5 +++++ src/markdown2pdf.hs | 6 ++++++ src/pandoc.hs | 7 ++++++- 5 files changed, 27 insertions(+), 4 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 88c425978..56c9bd542 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -36,14 +36,16 @@ inline links: > module Main where > import Text.Pandoc -> import qualified System.IO.UTF8 as U +> -- include the following two lines only if you're using ghc < 6.12: +> import Prelude hiding (getContents, putStrLn) +> import System.IO.UTF8 > > markdownToRST :: String -> String > markdownToRST = > (writeRST defaultWriterOptions {writerReferenceLinks = True}) . > readMarkdown defaultParserState > -> main = U.getContents >>= U.putStrLn . markdownToRST +> main = getContents >>= putStrLn . markdownToRST Note: all of the readers assume that the input text has @'\n'@ line endings. So if you get your input text from a web form, diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index b0748be07..ea3c69c2a 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -119,8 +119,13 @@ import Data.List ( find, isPrefixOf, intercalate ) import Network.URI ( parseURI, URI (..), isAllowedInURI ) import System.Directory import System.FilePath ( FilePath, () ) -import Prelude hiding ( putStrLn, writeFile, readFile, getContents ) +-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv +-- So we use System.IO.UTF8 only if we have an earlier version +#if MIN_VERSION_base(4,2,0) +#else +import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) import System.IO.UTF8 +#endif import Data.Generics import qualified Control.Monad.State as S import Control.Monad (join) diff --git a/src/hsmarkdown.hs b/src/hsmarkdown.hs index ed4695193..3f689d4ec 100644 --- a/src/hsmarkdown.hs +++ b/src/hsmarkdown.hs @@ -29,8 +29,13 @@ Wrapper around pandoc that emulates Markdown.pl as closely as possible. module Main where import System.Process import System.Environment ( getArgs ) +-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv +-- So we use System.IO.UTF8 only if we have an earlier version +#if MIN_VERSION_base(4,2,0) +#else import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) import System.IO.UTF8 +#endif import Control.Monad (forM_) main :: IO () diff --git a/src/markdown2pdf.hs b/src/markdown2pdf.hs index 815690f49..dc8421b28 100644 --- a/src/markdown2pdf.hs +++ b/src/markdown2pdf.hs @@ -9,8 +9,14 @@ import Control.Exception (tryJust, bracket) import System.IO (stderr) import System.IO.Error (isDoesNotExistError) import System.Environment ( getArgs, getProgName ) +-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv +-- So we use System.IO.UTF8 only if we have an earlier version +#if MIN_VERSION_base(4,2,0) +#else import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) import System.IO.UTF8 +#endif +import System.IO (hPutStrLn) import System.Exit (ExitCode (..), exitWith) import System.FilePath import System.Directory diff --git a/src/pandoc.hs b/src/pandoc.hs index ec915e2cc..6a6ccc70b 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -45,9 +45,14 @@ import System.Console.GetOpt import Data.Maybe ( fromMaybe ) import Data.Char ( toLower ) import Data.List ( intercalate, isSuffixOf ) +import System.IO ( stdout, stderr, hPutStrLn, hPutStr ) +-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv +-- So we use System.IO.UTF8 only if we have an earlier version +#if MIN_VERSION_base(4,2,0) +#else import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) -import System.IO ( stdout, stderr ) import System.IO.UTF8 +#endif #ifdef _CITEPROC import Text.CSL import Text.Pandoc.Biblio -- cgit v1.2.3