diff options
author | John MacFarlane <jgm@berkeley.edu> | 2010-05-06 20:29:44 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2010-05-06 22:28:28 -0700 |
commit | 1cc11e60863abdbe3d0e05b73f53d0377cd8fec2 (patch) | |
tree | fd8faa5c176f71dc9c55701ef3ccd4ce7a6a2de3 | |
parent | 7be82b45361e65939008bb93f0006c10dad946d5 (diff) | |
download | pandoc-1cc11e60863abdbe3d0e05b73f53d0377cd8fec2.tar.gz |
Use new UTF8 module in Shared, ODT, and the executables.
-rw-r--r-- | src/Text/Pandoc/ODT.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 16 | ||||
-rw-r--r-- | src/markdown2pdf.hs | 23 | ||||
-rw-r--r-- | src/pandoc.hs | 51 |
4 files changed, 35 insertions, 56 deletions
diff --git a/src/Text/Pandoc/ODT.hs b/src/Text/Pandoc/ODT.hs index d978c0cb4..a69d9d4e4 100644 --- a/src/Text/Pandoc/ODT.hs +++ b/src/Text/Pandoc/ODT.hs @@ -32,7 +32,6 @@ import Data.List ( find ) import System.FilePath ( (</>), takeFileName ) import qualified Data.ByteString.Lazy as B import Data.ByteString.Lazy.UTF8 ( fromString ) -import Prelude hiding ( writeFile, readFile ) import Codec.Archive.Zip import Control.Applicative ( (<$>) ) import Text.ParserCombinators.Parsec diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 26aff4250..274c969ca 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -112,6 +112,7 @@ module Text.Pandoc.Shared ( ) where import Text.Pandoc.Definition +import qualified Text.Pandoc.UTF8 as UTF8 (readFile, putStrLn) import Text.ParserCombinators.Parsec import Text.PrettyPrint.HughesPJ ( Doc, fsep, ($$), (<>), empty, isEmpty, text, nest ) import qualified Text.PrettyPrint.HughesPJ as PP @@ -123,13 +124,6 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI, escapeURIString, unEsca import Codec.Binary.UTF8.String ( encodeString, decodeString ) import System.Directory import System.FilePath ( (</>) ) --- 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) @@ -676,7 +670,7 @@ readWith parser state input = testStringWith :: (Show a) => GenParser Char ParserState a -> String -> IO () -testStringWith parser str = putStrLn $ show $ +testStringWith parser str = UTF8.putStrLn $ show $ readWith parser defaultParserState str -- | Parsing options. @@ -1074,6 +1068,6 @@ inDirectory path action = do readDataFile :: Maybe FilePath -> FilePath -> IO String readDataFile userDir fname = case userDir of - Nothing -> getDataFileName fname >>= readFile - Just u -> catch (readFile $ u </> fname) - (\_ -> getDataFileName fname >>= readFile) + Nothing -> getDataFileName fname >>= UTF8.readFile + Just u -> catch (UTF8.readFile $ u </> fname) + (\_ -> getDataFileName fname >>= UTF8.readFile) diff --git a/src/markdown2pdf.hs b/src/markdown2pdf.hs index d713ae263..c47bcf3c0 100644 --- a/src/markdown2pdf.hs +++ b/src/markdown2pdf.hs @@ -9,14 +9,7 @@ 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) -import System.IO (hPutStrLn) -#else -import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) -import System.IO.UTF8 -#endif +import qualified Text.Pandoc.UTF8 as UTF8 import System.Exit (ExitCode (..), exitWith) import System.FilePath import System.Directory @@ -57,7 +50,7 @@ runLatexRaw latexProgram file = do takeDirectory file, dropExtension file] >> return () let pdfFile = replaceExtension file "pdf" let logFile = replaceExtension file "log" - txt <- tryJust (guard . isDoesNotExistError) (readFile logFile) + txt <- tryJust (guard . isDoesNotExistError) (UTF8.readFile logFile) let checks = checkLatex $ either (const "") id txt case checks of -- err , bib , ref , msg @@ -122,13 +115,13 @@ runBibtex file = do exit :: String -> IO a exit x = do progName <- getProgName - hPutStrLn stderr $ progName ++ ": " ++ x + UTF8.hPutStrLn stderr $ progName ++ ": " ++ x exitWith $ ExitFailure 1 saveStdin :: FilePath -> IO (Either String FilePath) saveStdin file = do - text <- getContents - writeFile file text + text <- UTF8.getContents + UTF8.writeFile file text fileExist <- doesFileExist file case fileExist of False -> return $ Left $! "Could not create " ++ file @@ -137,7 +130,7 @@ saveStdin file = do saveOutput :: FilePath -> FilePath -> IO () saveOutput input output = do copyFile input output - hPutStrLn stderr $! "Created " ++ output + UTF8.hPutStrLn stderr $! "Created " ++ output main :: IO () main = bracket @@ -170,8 +163,8 @@ main = bracket any (\o -> (o ++ "=") `isPrefixOf` x) goodoptslong unless (all isGoodopt opts) $ do (code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] "" - putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:" - putStr $ unlines $ + UTF8.putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:" + UTF8.putStr $ unlines $ filter (\l -> any (`isInfixOf` l) goodoptslong) $ lines out exitWith code diff --git a/src/pandoc.hs b/src/pandoc.hs index 656099ce9..84e2b2a52 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -45,14 +45,7 @@ import Data.Char ( toLower, isDigit ) import Data.List ( intercalate, isSuffixOf ) import System.Directory ( getAppUserDataDirectory ) import System.IO ( stdout, stderr ) --- 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) -import System.IO ( hPutStr, hPutStrLn ) -#else -import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents ) -import System.IO.UTF8 -#endif +import qualified Text.Pandoc.UTF8 as UTF8 #ifdef _CITEPROC import Text.CSL import Text.Pandoc.Biblio @@ -344,7 +337,7 @@ options = "references" -> return ReferenceObfuscation "javascript" -> return JavascriptObfuscation "none" -> return NoObfuscation - _ -> hPutStrLn stderr ("Error: Unknown obfuscation method: " ++ arg) >> + _ -> UTF8.hPutStrLn stderr ("Error: Unknown obfuscation method: " ++ arg) >> exitWith (ExitFailure 6) return opt { optEmailObfuscation = method }) "none|javascript|references") @@ -378,7 +371,7 @@ options = return opt{ optTransforms = headerShift shift : oldTransforms } else do - hPutStrLn stderr $ "base-header-level must be a number >= 1" + UTF8.hPutStrLn stderr $ "base-header-level must be a number >= 1" exitWith $ ExitFailure 19) "LEVEL") "" -- "Headers base level" @@ -386,7 +379,7 @@ options = , Option "" ["template"] (ReqArg (\arg opt -> do - text <- readFile arg + text <- UTF8.readFile arg return opt{ optTemplate = text, optStandalone = True }) "FILENAME") @@ -400,7 +393,7 @@ options = let newvars = optVariables opt ++ [(k,v)] return opt{ optVariables = newvars } _ -> do - hPutStrLn stderr $ "Could not parse `" ++ arg ++ "' as a key/value pair (k=v or k:v)" + UTF8.hPutStrLn stderr $ "Could not parse `" ++ arg ++ "' as a key/value pair (k=v or k:v)" exitWith $ ExitFailure 17) "FILENAME") "" -- "Use custom template" @@ -418,7 +411,7 @@ options = , Option "H" ["include-in-header"] (ReqArg (\arg opt -> do - text <- readFile arg + text <- UTF8.readFile arg -- add new ones to end, so they're included in order specified let newvars = optVariables opt ++ [("header-includes",text)] return opt { optVariables = newvars, @@ -429,7 +422,7 @@ options = , Option "B" ["include-before-body"] (ReqArg (\arg opt -> do - text <- readFile arg + text <- UTF8.readFile arg -- add new ones to end, so they're included in order specified let newvars = optVariables opt ++ [("include-before",text)] return opt { optVariables = newvars, @@ -440,7 +433,7 @@ options = , Option "A" ["include-after-body"] (ReqArg (\arg opt -> do - text <- readFile arg + text <- UTF8.readFile arg -- add new ones to end, so they're included in order specified let newvars = optVariables opt ++ [("include-after",text)] return opt { optVariables = newvars, @@ -451,7 +444,7 @@ options = , Option "C" ["custom-header"] (ReqArg (\arg opt -> do - text <- readFile arg + text <- UTF8.readFile arg let newVars = ("legacy-header", text) : optVariables opt return opt { optVariables = newVars , optStandalone = True }) @@ -479,7 +472,7 @@ options = (\arg _ -> do templ <- getDefaultTemplate Nothing arg case templ of - Right t -> hPutStr stdout t + Right t -> UTF8.hPutStr stdout t Left e -> error $ show e exitWith ExitSuccess) "FORMAT") @@ -521,7 +514,7 @@ options = (NoArg (\_ -> do prg <- getProgName - hPutStrLn stdout (prg ++ " " ++ pandocVersion ++ compileInfo ++ + UTF8.hPutStrLn stdout (prg ++ " " ++ pandocVersion ++ compileInfo ++ copyrightMessage) exitWith ExitSuccess )) "" -- "Print version" @@ -530,7 +523,7 @@ options = (NoArg (\_ -> do prg <- getProgName - hPutStr stdout (usageMessage prg options) + UTF8.hPutStr stdout (usageMessage prg options) exitWith ExitSuccess )) "" -- "Show help" ] @@ -603,8 +596,8 @@ main = do unless (null errors) $ do name <- getProgName - mapM_ (\e -> hPutStr stderr (name ++ ": ") >> hPutStr stderr e) errors - hPutStrLn stderr $ "Try " ++ name ++ " --help for more information." + mapM_ (\e -> UTF8.hPutStr stderr (name ++ ": ") >> UTF8.hPutStr stderr e) errors + UTF8.hPutStrLn stderr $ "Try " ++ name ++ " --help for more information." exitWith $ ExitFailure 2 let defaultOpts' = if compatMode @@ -653,13 +646,13 @@ main = do } = opts when dumpArgs $ - do hPutStrLn stdout outputFile - mapM_ (\arg -> hPutStrLn stdout arg) args + do UTF8.hPutStrLn stdout outputFile + mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args exitWith ExitSuccess -- warn about deprecated options case lookup "legacy-header" variables of - Just _ -> hPutStrLn stderr $ + Just _ -> UTF8.hPutStrLn stderr $ "Warning: The -C/--custom-header is deprecated.\n" ++ "Please transition to using --template instead." Nothing -> return () @@ -765,7 +758,7 @@ main = do writerIdentifierPrefix = idPrefix } when (isNonTextOutput writerName' && outputFile == "-") $ - do hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++ + do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++ "Specify an output file using the -o option.") exitWith $ ExitFailure 5 @@ -775,10 +768,10 @@ main = do let readSources [] = mapM readSource ["-"] readSources srcs = mapM readSource srcs - readSource "-" = getContents + readSource "-" = UTF8.getContents readSource src = case parseURI src of Just u -> readURI u - Nothing -> readFile src + Nothing -> UTF8.readFile src readURI uri = simpleHTTP (mkRequest GET uri) >>= getResponseBody >>= return . toString -- treat all as UTF8 @@ -800,5 +793,5 @@ main = do case writerName' of "odt" -> saveOpenDocumentAsODT datadir outputFile sourceDirRelative referenceODT writerOutput _ -> if outputFile == "-" - then putStr writerOutput - else writeFile outputFile writerOutput + then UTF8.putStr writerOutput + else UTF8.writeFile outputFile writerOutput |