aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Compat
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Compat')
-rw-r--r--src/Text/Pandoc/Compat/Directory.hs21
-rw-r--r--src/Text/Pandoc/Compat/Except.hs37
-rw-r--r--src/Text/Pandoc/Compat/Monoid.hs17
-rw-r--r--src/Text/Pandoc/Compat/TagSoupEntity.hs15
-rw-r--r--src/Text/Pandoc/Compat/Time.hs12
5 files changed, 12 insertions, 90 deletions
diff --git a/src/Text/Pandoc/Compat/Directory.hs b/src/Text/Pandoc/Compat/Directory.hs
deleted file mode 100644
index 61dd5c525..000000000
--- a/src/Text/Pandoc/Compat/Directory.hs
+++ /dev/null
@@ -1,21 +0,0 @@
-{-# LANGUAGE CPP #-}
-module Text.Pandoc.Compat.Directory ( getModificationTime )
- where
-
-#if MIN_VERSION_directory(1,2,0)
-import System.Directory
-
-
-#else
-import qualified System.Directory as S
-import Data.Time.Clock (UTCTime)
-import Data.Time.Clock.POSIX
-import System.Time
-
-getModificationTime :: FilePath -> IO UTCTime
-getModificationTime fp = convert `fmap` S.getModificationTime fp
- where
- convert (TOD x _) = posixSecondsToUTCTime (realToFrac x)
-
-#endif
-
diff --git a/src/Text/Pandoc/Compat/Except.hs b/src/Text/Pandoc/Compat/Except.hs
deleted file mode 100644
index 9ce7c0d36..000000000
--- a/src/Text/Pandoc/Compat/Except.hs
+++ /dev/null
@@ -1,37 +0,0 @@
-{-# LANGUAGE CPP #-}
-module Text.Pandoc.Compat.Except ( ExceptT
- , Except
- , Error(..)
- , runExceptT
- , runExcept
- , MonadError
- , throwError
- , catchError )
- where
-
-#if MIN_VERSION_mtl(2,2,1)
-import Control.Monad.Except
-
-class Error a where
- noMsg :: a
- strMsg :: String -> a
-
- noMsg = strMsg ""
- strMsg _ = noMsg
-
-#else
-import Control.Monad.Error
-import Control.Monad.Identity (Identity, runIdentity)
-
-type ExceptT = ErrorT
-
-type Except s a = ErrorT s Identity a
-
-runExceptT :: ExceptT e m a -> m (Either e a)
-runExceptT = runErrorT
-
-runExcept :: ExceptT e Identity a -> Either e a
-runExcept = runIdentity . runExceptT
-#endif
-
-
diff --git a/src/Text/Pandoc/Compat/Monoid.hs b/src/Text/Pandoc/Compat/Monoid.hs
deleted file mode 100644
index 4daceb8e1..000000000
--- a/src/Text/Pandoc/Compat/Monoid.hs
+++ /dev/null
@@ -1,17 +0,0 @@
-{-# LANGUAGE CPP #-}
-module Text.Pandoc.Compat.Monoid ( (<>) )
- where
-
-#if MIN_VERSION_base(4,5,0)
-import Data.Monoid ((<>))
-
-#else
-import Data.Monoid
-
-infixr 6 <>
-
---- | An infix synonym for 'mappend'.
-(<>) :: Monoid m => m -> m -> m
-(<>) = mappend
-{-# INLINE (<>) #-}
-#endif
diff --git a/src/Text/Pandoc/Compat/TagSoupEntity.hs b/src/Text/Pandoc/Compat/TagSoupEntity.hs
deleted file mode 100644
index 80985aef9..000000000
--- a/src/Text/Pandoc/Compat/TagSoupEntity.hs
+++ /dev/null
@@ -1,15 +0,0 @@
-{-# LANGUAGE CPP #-}
-module Text.Pandoc.Compat.TagSoupEntity (lookupEntity
- ) where
-
-import qualified Text.HTML.TagSoup.Entity as TE
-
-lookupEntity :: String -> Maybe Char
-#if MIN_VERSION_tagsoup(0,13,0)
-lookupEntity = str2chr . TE.lookupEntity
- where str2chr :: Maybe String -> Maybe Char
- str2chr (Just [c]) = Just c
- str2chr _ = Nothing
-#else
-lookupEntity = TE.lookupEntity
-#endif
diff --git a/src/Text/Pandoc/Compat/Time.hs b/src/Text/Pandoc/Compat/Time.hs
index aa08ca224..b1cde82a4 100644
--- a/src/Text/Pandoc/Compat/Time.hs
+++ b/src/Text/Pandoc/Compat/Time.hs
@@ -1,4 +1,16 @@
{-# LANGUAGE CPP #-}
+
+{-
+This compatibility module is needed because, in time 1.5, the
+`defaultTimeLocale` function was moved from System.Locale (in the
+old-locale library) into Data.Time.
+
+We support both behaviors because time 1.4 is a boot library for GHC
+7.8. time 1.5 is a boot library for GHC 7.10.
+
+When support is dropped for GHC 7.8, this module may be obsoleted.
+-}
+
#if MIN_VERSION_time(1,5,0)
module Text.Pandoc.Compat.Time (
module Data.Time