Remove blaze-html CPP conditional.

This tests for a min value >= 0.5. But we have a lower bound of 0.5 in
pandoc.cabal, so the test will always pass.

(If we bump the lower bound to 0.5.1, we can remove a conditional in the
HTML writer as well.)
This commit is contained in:
Jesse Rosenthal 2016-09-03 08:32:29 -04:00
parent df1ca2b1a5
commit 7d9f2d3657

View file

@ -1,4 +1,4 @@
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP, {-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
OverloadedStrings, GeneralizedNewtypeDeriving #-} OverloadedStrings, GeneralizedNewtypeDeriving #-}
{- {-
Copyright (C) 2009-2016 John MacFarlane <jgm@berkeley.edu> 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 qualified Data.HashMap.Strict as H
import Data.Foldable (toList) import Data.Foldable (toList)
import qualified Control.Exception.Extensible as E (try, IOException) 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.Html (Html)
import Text.Blaze.Internal (preEscapedText) import Text.Blaze.Internal (preEscapedText)
#else
import Text.Blaze (preEscapedText, Html)
#endif
import Data.ByteString.Lazy (ByteString, fromChunks) import Data.ByteString.Lazy (ByteString, fromChunks)
import Text.Pandoc.Shared (readDataFileUTF8, ordNub) import Text.Pandoc.Shared (readDataFileUTF8, ordNub)
import Data.Vector ((!?)) import Data.Vector ((!?))