Drop support for ghc < 8.
This commit is contained in:
parent
a43c0bf54b
commit
3ecc8d154b
5 changed files with 2 additions and 18 deletions
|
@ -144,7 +144,7 @@ Please follow these guidelines:
|
|||
9. It is better not to introduce new dependencies. Dependencies on
|
||||
external C libraries should especially be avoided.
|
||||
|
||||
10. We aim for compatibility with ghc versions from 7.10.3 to the
|
||||
10. We aim for compatibility with ghc versions from 8.0 to the
|
||||
latest release. All pull requests and commits are tested
|
||||
automatically on CircleCI.
|
||||
|
||||
|
|
|
@ -11,8 +11,7 @@ bug-reports: https://github.com/jgm/pandoc/issues
|
|||
stability: alpha
|
||||
homepage: https://pandoc.org
|
||||
category: Text
|
||||
tested-with: GHC == 7.10.3, GHC == 8.0.2, GHC == 8.2.2, GHC == 8.4.4,
|
||||
GHC == 8.6.3
|
||||
tested-with: GHC == 8.0.2, GHC == 8.2.2, GHC == 8.4.4, GHC == 8.6.3
|
||||
synopsis: Conversion between markup formats
|
||||
description: Pandoc is a Haskell library for converting from one markup
|
||||
format to another, and a command-line tool that uses
|
||||
|
|
|
@ -9,10 +9,6 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
#if MIN_VERSION_base(4,8,0)
|
||||
#else
|
||||
{-# LANGUAGE OverlappingInstances #-}
|
||||
#endif
|
||||
{- |
|
||||
Module : Text.Pandoc.Class
|
||||
Copyright : Copyright (C) 2016-17 Jesse Rosenthal, John MacFarlane
|
||||
|
@ -1041,11 +1037,7 @@ instance (MonadTrans t, PandocMonad m, Functor (t m),
|
|||
putCommonState = lift . putCommonState
|
||||
logOutput = lift . logOutput
|
||||
|
||||
#if MIN_VERSION_base(4,8,0)
|
||||
instance {-# OVERLAPS #-} PandocMonad m => PandocMonad (ParsecT s st m) where
|
||||
#else
|
||||
instance PandocMonad m => PandocMonad (ParsecT s st m) where
|
||||
#endif
|
||||
lookupEnv = lift . lookupEnv
|
||||
getCurrentTime = lift getCurrentTime
|
||||
getCurrentTimeZone = lift getCurrentTimeZone
|
||||
|
|
|
@ -34,11 +34,7 @@ import System.FilePath
|
|||
import System.IO (stdout)
|
||||
import System.IO.Temp (withSystemTempDirectory, withTempDirectory,
|
||||
withTempFile)
|
||||
#if MIN_VERSION_base(4,8,3)
|
||||
import System.IO.Error (IOError, isDoesNotExistError)
|
||||
#else
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
#endif
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Error (PandocError (PandocPDFProgramNotFoundError))
|
||||
import Text.Pandoc.MIME (getMimeType)
|
||||
|
|
|
@ -79,9 +79,6 @@ import Text.Pandoc.Readers.Docx.Parse
|
|||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Walk
|
||||
import Text.TeXMath (writeTeX)
|
||||
#if !(MIN_VERSION_base(4,8,0))
|
||||
import Data.Traversable (traverse)
|
||||
#endif
|
||||
import Control.Monad.Except (throwError)
|
||||
import Text.Pandoc.Class (PandocMonad)
|
||||
import qualified Text.Pandoc.Class as P
|
||||
|
|
Loading…
Add table
Reference in a new issue