aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--man/make-pandoc-man-pages.hs1
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Pretty.hs2
-rw-r--r--src/Text/Pandoc/UTF8.hs1
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs6
5 files changed, 4 insertions, 10 deletions
diff --git a/man/make-pandoc-man-pages.hs b/man/make-pandoc-man-pages.hs
index eca1276eb..008294433 100644
--- a/man/make-pandoc-man-pages.hs
+++ b/man/make-pandoc-man-pages.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
-- Create pandoc.1 man and pandoc_markdown.5 man pages from README
import Text.Pandoc
import qualified Text.Pandoc.UTF8 as UTF8
diff --git a/pandoc.cabal b/pandoc.cabal
index 7d4bccc41..7f12a44ae 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -277,7 +277,6 @@ Library
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
Ghc-Prof-Options: -auto-all -caf-all -rtsopts
Default-Language: Haskell98
- Default-Extensions: CPP
Other-Extensions: PatternGuards, OverloadedStrings,
ScopedTypeVariables, GeneralizedNewtypeDeriving,
RelaxedPolyRec, DeriveDataTypeable, TypeSynonymInstances,
@@ -357,7 +356,6 @@ Executable pandoc
if os(windows)
Cpp-options: -D_WINDOWS
Default-Language: Haskell98
- Default-Extensions: CPP
Other-Extensions: PatternGuards, OverloadedStrings,
ScopedTypeVariables, GeneralizedNewtypeDeriving,
RelaxedPolyRec, DeriveDataTypeable, TypeSynonymInstances,
@@ -377,7 +375,6 @@ Executable make-pandoc-man-pages
old-time >= 1.0 && < 1.2,
time >= 1.2 && < 1.5
Default-Language: Haskell98
- Default-Extensions: CPP
Test-Suite test-pandoc
Type: exitcode-stdio-1.0
@@ -415,7 +412,6 @@ Test-Suite test-pandoc
Tests.Writers.LaTeX
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
Default-Language: Haskell98
- Default-Extensions: CPP
benchmark benchmark-pandoc
Type: exitcode-stdio-1.0
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index 21121a506..faf2a6797 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-}
{-
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index 9fa743cd9..229442543 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index e625931fc..fb756f196 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE PatternGuards, CPP #-}
{-
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
@@ -62,11 +62,7 @@ import Text.Pandoc.MIME (getMimeType)
import Prelude hiding (catch)
#endif
import Control.Exception (catch, SomeException)
-#if MIN_VERSION_blaze_html(0,5,0)
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
-#else
-import Text.Blaze.Renderer.Utf8 (renderHtml)
-#endif
-- A Chapter includes a list of blocks and maybe a section
-- number offset. Note, some chapters are unnumbered. The section