aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-08-03 08:43:28 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-08-03 08:43:28 +0000
commited4b00399778204bc589135e005620c40c988258 (patch)
tree0b02b65bed4f08f67281e47ee6254163366e4c41
parentb63d1c5e3200909eefe5bbd3bf0d6092593a4cb2 (diff)
downloadpandoc-ed4b00399778204bc589135e005620c40c988258.tar.gz
Added 'utf8' configuration flag to pandoc.cabal.
This makes it possible to compile pandoc without utf8, using '-f-utf8' at configuration time. Utf-8 support is still the default. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1373 788f1e2b-df1e-0410-8736-df70ead52e1b
-rw-r--r--Main.hs12
-rw-r--r--Text/Pandoc/ODT.hs12
-rw-r--r--pandoc.cabal10
3 files changed, 25 insertions, 9 deletions
diff --git a/Main.hs b/Main.hs
index 45d524acd..8abb7c55f 100644
--- a/Main.hs
+++ b/Main.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-
Copyright (C) 2006-8 John MacFarlane <jgm@berkeley.edu>
@@ -37,12 +38,15 @@ import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath ( takeExtension, takeDirectory )
import System.Console.GetOpt
-import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
-import System.IO ( stdout, stderr )
-import System.IO.UTF8
import Data.Maybe ( fromMaybe )
import Data.Char ( toLower )
-import Control.Monad ( (>>=) )
+import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
+#ifdef UTF_8
+import System.IO.UTF8
+import System.IO ( stdout, stderr )
+#else
+import System.IO
+#endif
copyrightMessage :: String
copyrightMessage = "\nCopyright (C) 2006-7 John MacFarlane\n" ++
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs
index 08ecf7d06..b44cb303f 100644
--- a/Text/Pandoc/ODT.hs
+++ b/Text/Pandoc/ODT.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TemplateHaskell, CPP #-}
{-
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
@@ -32,9 +32,6 @@ module Text.Pandoc.ODT ( saveOpenDocumentAsODT ) where
import Text.Pandoc.TH ( binaryContentsOf )
import Data.Maybe ( fromJust )
import Data.List ( partition, intersperse )
-import Prelude hiding ( writeFile, readFile, getContents )
-import System.IO.UTF8
-import System.IO ( stderr )
import System.Directory
import System.FilePath ( (</>), takeDirectory, takeFileName, splitDirectories )
import System.Process ( runProcess, waitForProcess )
@@ -45,6 +42,13 @@ import Text.Pandoc.Shared ( withTempDir )
import Network.URI ( isURI )
import qualified Data.ByteString as B ( writeFile, pack )
import Data.ByteString.Internal ( c2w )
+import Prelude hiding ( writeFile, readFile )
+#ifdef UTF_8
+import System.IO.UTF8
+import System.IO ( stderr )
+#else
+import System.IO
+#endif
-- | Produce an ODT file from OpenDocument XML.
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
diff --git a/pandoc.cabal b/pandoc.cabal
index c90339577..fd5ab1e9c 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -64,6 +64,9 @@ Flag executable
Flag library
Description: Build the pandoc library.
Default: True
+Flag utf8
+ Description: Compile in support for UTF-8 input and output.
+ Default: True
Library
if flag(splitBase)
@@ -73,7 +76,10 @@ Library
if flag(highlighting)
Build-depends: highlighting-kate
cpp-options: -DHIGHLIGHTING
- Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, utf8-string,
+ if flag(utf8)
+ Build-depends: utf8-string
+ cpp-options: -DUTF_8
+ Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory,
template-haskell, bytestring
Hs-Source-Dirs: .
Exposed-Modules: Text.Pandoc,
@@ -125,6 +131,8 @@ Executable pandoc
Ghc-Options: -O2 -Wall -threaded
Ghc-Prof-Options: -auto-all
+ if flag(utf8)
+ cpp-options: -DUTF_8
if flag(executable)
Buildable: True
else