aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Templates.hs6
1 files changed, 1 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 5ac84018a..d111b3efa 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP,
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
OverloadedStrings, GeneralizedNewtypeDeriving #-}
{-
Copyright (C) 2009-2016 John MacFarlane <jgm@berkeley.edu>
@@ -108,12 +108,8 @@ import qualified Data.Map as M
import qualified Data.HashMap.Strict as H
import Data.Foldable (toList)
import qualified Control.Exception.Extensible as E (try, IOException)
-#if MIN_VERSION_blaze_html(0,5,0)
import Text.Blaze.Html (Html)
import Text.Blaze.Internal (preEscapedText)
-#else
-import Text.Blaze (preEscapedText, Html)
-#endif
import Data.ByteString.Lazy (ByteString, fromChunks)
import Text.Pandoc.Shared (readDataFileUTF8, ordNub)
import Data.Vector ((!?))