aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 16:48:21 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 16:48:21 +0000
commitaab574f9ef78792e53bfc55aa58635ecaf8b2a90 (patch)
tree28ec7452cf972478380b25f0da2487f55354e1b4 /src/Text
parent1b3d5896c7ffe976daac0fb3057526e52c0cfb44 (diff)
downloadpandoc-aab574f9ef78792e53bfc55aa58635ecaf8b2a90.tar.gz
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
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc.hs6
-rw-r--r--src/Text/Pandoc/Shared.hs7
2 files changed, 10 insertions, 3 deletions
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)