From c613dbde01e8145ae10e0d85a8038cc336ea9ad0 Mon Sep 17 00:00:00 2001
From: Jesse Rosenthal <jrosenthal@jhu.edu>
Date: Thu, 1 Sep 2016 07:07:03 -0400
Subject: Remove unnecessary CPP condition in UTF8

Base 4.4 is ghc 7.2, so we don't have to worry about getting a lower version.
---
 src/Text/Pandoc/UTF8.hs | 9 ++-------
 1 file changed, 2 insertions(+), 7 deletions(-)

(limited to 'src/Text')

diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index 87ed5312b..62a662029 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
 {-
 Copyright (C) 2010-2016 John MacFarlane <jgm@berkeley.edu>
 
@@ -116,11 +115,7 @@ fromStringLazy :: String -> BL.ByteString
 fromStringLazy = TL.encodeUtf8 . TL.pack
 
 encodePath :: FilePath -> FilePath
-decodeArg :: String -> String
-#if MIN_VERSION_base(4,4,0)
 encodePath = id
+
+decodeArg :: String -> String
 decodeArg = id
-#else
-encodePath = B.unpack . fromString
-decodeArg = toString . B.pack
-#endif
-- 
cgit v1.2.3