aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-30 16:03:06 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-30 16:03:06 -0800
commite42f3465164e7d4776c771cc36b1cc1ebfec3651 (patch)
tree203fc50ab4100782594fa196cd184ef373aad97c
parentc2998f5e902a0a96eb4fa0f3d24b89fe1bb5579d (diff)
parentb1b6d0f8590dceea588495f316ef1eac9f4c1078 (diff)
downloadpandoc-e42f3465164e7d4776c771cc36b1cc1ebfec3651.tar.gz
Merge branch 'lineend'
-rw-r--r--src/Text/Pandoc/UTF8.hs45
-rw-r--r--src/pandoc.hs32
2 files changed, 58 insertions, 19 deletions
diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index eba79c734..6d9ac1d1a 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -25,7 +25,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Stability : alpha
Portability : portable
-UTF-8 aware string IO functions that will work with GHC 6.10 or 6.12.
+UTF-8 aware string IO functions that will work with GHC 6.10, 6.12, or 7.
-}
module Text.Pandoc.UTF8 ( readFile
, writeFile
@@ -34,9 +34,46 @@ module Text.Pandoc.UTF8 ( readFile
, putStrLn
, hPutStr
, hPutStrLn
+ , hGetContents
)
where
+
+#ifdef MIN_VERSION_base(4,2,0)
+
+import System.IO hiding (readFile, writeFile, getContents,
+ putStr, putStrLn, hPutStr, hPutStrLn, hGetContents)
+import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn )
+import qualified System.IO as IO
+
+readFile :: FilePath -> IO String
+readFile f = do
+ h <- openFile f ReadMode
+ hGetContents h
+
+writeFile :: FilePath -> String -> IO ()
+writeFile f s = withFile f WriteMode $ \h -> hPutStr h s
+
+getContents :: IO String
+getContents = hGetContents stdin
+
+putStr :: String -> IO ()
+putStr s = hPutStr stdout s
+
+putStrLn :: String -> IO ()
+putStrLn s = hPutStrLn stdout s
+
+hPutStr :: Handle -> String -> IO ()
+hPutStr h s = hSetEncoding h utf8 >> IO.hPutStr h s
+
+hPutStrLn :: Handle -> String -> IO ()
+hPutStrLn h s = hSetEncoding h utf8 >> IO.hPutStrLn h s
+
+hGetContents :: Handle -> IO String
+hGetContents h = hSetEncoding h utf8_bom >> IO.hGetContents h
+
+#else
+
import qualified Data.ByteString as B
import Codec.Binary.UTF8.String (encodeString)
import Data.ByteString.UTF8 (toString, fromString)
@@ -44,6 +81,7 @@ import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn)
import System.IO (Handle)
import Control.Monad (liftM)
+
bom :: B.ByteString
bom = B.pack [0xEF, 0xBB, 0xBF]
@@ -60,6 +98,9 @@ writeFile f = B.writeFile (encodeString f) . fromString
getContents :: IO String
getContents = liftM (toString . stripBOM) B.getContents
+hGetContents :: Handle -> IO String
+hGetContents h = liftM (toString . stripBOM) (B.hGetContents h)
+
putStr :: String -> IO ()
putStr = B.putStr . fromString
@@ -71,3 +112,5 @@ hPutStr h = B.hPutStr h . fromString
hPutStrLn :: Handle -> String -> IO ()
hPutStrLn h s = hPutStr h (s ++ "\n")
+
+#endif
diff --git a/src/pandoc.hs b/src/pandoc.hs
index e3d7b8c4e..c0f457449 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -51,7 +51,7 @@ import Control.Monad (when, unless, liftM)
import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
import Network.URI (parseURI, isURI, URI(..))
import qualified Data.ByteString.Lazy as B
-import Data.ByteString.Lazy.UTF8 (toString, fromString)
+import Data.ByteString.Lazy.UTF8 (toString )
import Codec.Binary.UTF8.String (decodeString, encodeString)
copyrightMessage :: String
@@ -713,14 +713,6 @@ main = do
Just r -> return r
Nothing -> error ("Unknown reader: " ++ readerName')
- let writer = case lookup writerName' writers of
- Nothing | writerName' == "epub" -> writeEPUB epubStylesheet
- Nothing | writerName' == "odt" -> writeODT referenceODT
- Just r -> \o ->
- return . fromString . r o
- Nothing -> error $ "Unknown writer: " ++
- writerName'
-
templ <- getDefaultTemplate datadir writerName'
let defaultTemplate = case templ of
Right t -> t
@@ -855,12 +847,16 @@ main = do
processBiblio cslfile' refs doc1
else return doc1
- writerOutput <- writer writerOptions doc2
-
- let writerOutput' = if standalone'
- then writerOutput
- else writerOutput `B.snoc` 10
-
- if outputFile == "-"
- then B.putStr writerOutput'
- else B.writeFile (encodeString outputFile) writerOutput'
+ case lookup writerName' writers of
+ Nothing | writerName' == "epub" ->
+ writeEPUB epubStylesheet writerOptions doc2
+ >>= B.writeFile (encodeString outputFile)
+ Nothing | writerName' == "odt" ->
+ writeODT referenceODT writerOptions doc2
+ >>= B.writeFile (encodeString outputFile)
+ Just r -> writerFn outputFile result
+ where writerFn "-" = UTF8.putStr
+ writerFn f = UTF8.writeFile f
+ result = r writerOptions doc2 ++
+ ['\n' | not standalone']
+ Nothing -> error $ "Unknown writer: " ++ writerName'