From 99f3f3931282c9e2836b93299c1b656173bf162e Mon Sep 17 00:00:00 2001 From: Herbert Valerio Riedel <hvr@gnu.org> Date: Sun, 23 Jun 2019 13:35:15 +0200 Subject: [PATCH] Tidy up extensions and CPP handling We don't have the means anymore to properly test GHC 6.12 anymore and code has bitrotten to the point where it makes no sense to even advertise support for GHC 6.12 anymore. Starting with this commit `text` now explicitly requires a Haskell2010+ compiler and the CPP and compiler dependency specification is updated to reflect this. --- Data/Text.hs | 9 ++---- Data/Text/Array.hs | 6 ++-- Data/Text/Encoding.hs | 6 ++-- Data/Text/Foreign.hs | 2 +- Data/Text/Internal/Functions.hs | 2 -- Data/Text/Internal/Fusion/Common.hs | 2 +- Data/Text/Internal/Fusion/Size.hs | 2 +- Data/Text/Internal/IO.hs | 2 +- Data/Text/Lazy.hs | 9 ++---- text.cabal | 49 ++++++++++++++++++++++++----- 10 files changed, 57 insertions(+), 32 deletions(-) diff --git a/Data/Text.hs b/Data/Text.hs index ce953f0e..3e6693b3 100644 --- a/Data/Text.hs +++ b/Data/Text.hs @@ -1,11 +1,8 @@ -{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples, TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} #if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} #endif -#if __GLASGOW_HASKELL__ >= 708 -{-# LANGUAGE TypeFamilies #-} -#endif -- Using TemplateHaskell in text unconditionally is unacceptable, as -- it's a GHC boot library. TemplateHaskellQuotes was added in 8.0, so -- this would seem to be a problem. However, GHC's policy of only @@ -252,7 +249,7 @@ import qualified Data.Text.Lazy as L import Data.Int (Int64) #endif import GHC.Base (eqInt, neInt, gtInt, geInt, ltInt, leInt) -#if __GLASGOW_HASKELL__ >= 708 +#if MIN_VERSION_base(4,7,0) import qualified GHC.Exts as Exts #endif import qualified Language.Haskell.TH.Lib as TH @@ -384,7 +381,7 @@ instance Monoid Text where instance IsString Text where fromString = pack -#if __GLASGOW_HASKELL__ >= 708 +#if MIN_VERSION_base(4,7,0) -- | @since 1.2.0.0 instance Exts.IsList Text where type Item Text = Char diff --git a/Data/Text/Array.hs b/Data/Text/Array.hs index 849c6338..cf5cb8cb 100644 --- a/Data/Text/Array.hs +++ b/Data/Text/Array.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, MagicHash, Rank2Types, +{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, RecordWildCards, UnboxedTuples, UnliftedFFITypes #-} {-# OPTIONS_GHC -fno-warn-unused-matches #-} -- | @@ -58,7 +58,7 @@ if (_k_) < 0 || (_k_) >= (_len_) then error ("Data.Text.Array." ++ (_func_) ++ " #if defined(ASSERTS) import Control.Exception (assert) #endif -#if __GLASGOW_HASKELL__ >= 702 +#if MIN_VERSION_base(4,4,0) import Control.Monad.ST.Unsafe (unsafeIOToST) #else import Control.Monad.ST (unsafeIOToST) @@ -66,7 +66,7 @@ import Control.Monad.ST (unsafeIOToST) import Data.Bits ((.&.), xor) import Data.Text.Internal.Unsafe (inlinePerformIO) import Data.Text.Internal.Unsafe.Shift (shiftL, shiftR) -#if __GLASGOW_HASKELL__ >= 703 +#if MIN_VERSION_base(4,5,0) import Foreign.C.Types (CInt(CInt), CSize(CSize)) #else import Foreign.C.Types (CInt, CSize) diff --git a/Data/Text/Encoding.hs b/Data/Text/Encoding.hs index fd0f1e42..d8936796 100644 --- a/Data/Text/Encoding.hs +++ b/Data/Text/Encoding.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, GeneralizedNewtypeDeriving, MagicHash, +{-# LANGUAGE BangPatterns, CPP, GeneralizedNewtypeDeriving, MagicHash, UnliftedFFITypes #-} #if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} @@ -59,7 +59,7 @@ module Data.Text.Encoding , encodeUtf8BuilderEscaped ) where -#if __GLASGOW_HASKELL__ >= 702 +#if MIN_VERSION_base(4,4,0) import Control.Monad.ST.Unsafe (unsafeIOToST, unsafeSTToIO) #else import Control.Monad.ST (unsafeIOToST, unsafeSTToIO) @@ -78,7 +78,7 @@ import Data.Text.Internal.Unsafe.Shift (shiftR) import Data.Text.Show () import Data.Text.Unsafe (unsafeDupablePerformIO) import Data.Word (Word8, Word32) -#if __GLASGOW_HASKELL__ >= 703 +#if MIN_VERSION_base(4,5,0) import Foreign.C.Types (CSize(CSize)) #else import Foreign.C.Types (CSize) diff --git a/Data/Text/Foreign.hs b/Data/Text/Foreign.hs index 0dad97e1..2e9feab6 100644 --- a/Data/Text/Foreign.hs +++ b/Data/Text/Foreign.hs @@ -34,7 +34,7 @@ module Data.Text.Foreign #if defined(ASSERTS) import Control.Exception (assert) #endif -#if __GLASGOW_HASKELL__ >= 702 +#if MIN_VERSION_base(4,4,0) import Control.Monad.ST.Unsafe (unsafeIOToST) #else import Control.Monad.ST (unsafeIOToST) diff --git a/Data/Text/Internal/Functions.hs b/Data/Text/Internal/Functions.hs index f002ccc0..2973b1e3 100644 --- a/Data/Text/Internal/Functions.hs +++ b/Data/Text/Internal/Functions.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP, DeriveDataTypeable #-} - -- | -- Module : Data.Text.Internal.Functions -- Copyright : 2010 Bryan O'Sullivan diff --git a/Data/Text/Internal/Fusion/Common.hs b/Data/Text/Internal/Fusion/Common.hs index 260dd3f4..a8008637 100644 --- a/Data/Text/Internal/Fusion/Common.hs +++ b/Data/Text/Internal/Fusion/Common.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternGuards, BangPatterns, MagicHash, Rank2Types #-} +{-# LANGUAGE BangPatterns, MagicHash, Rank2Types #-} -- | -- Module : Data.Text.Internal.Fusion.Common -- Copyright : (c) Bryan O'Sullivan 2009, 2012 diff --git a/Data/Text/Internal/Fusion/Size.hs b/Data/Text/Internal/Fusion/Size.hs index 00cf6999..50118c97 100644 --- a/Data/Text/Internal/Fusion/Size.hs +++ b/Data/Text/Internal/Fusion/Size.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, PatternGuards #-} +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-missing-methods #-} -- | -- Module : Data.Text.Internal.Fusion.Internal diff --git a/Data/Text/Internal/IO.hs b/Data/Text/Internal/IO.hs index 1cf90961..8a26f87b 100644 --- a/Data/Text/Internal/IO.hs +++ b/Data/Text/Internal/IO.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, RecordWildCards #-} +{-# LANGUAGE BangPatterns, RecordWildCards #-} -- | -- Module : Data.Text.Internal.IO -- Copyright : (c) 2009, 2010 Bryan O'Sullivan, diff --git a/Data/Text/Lazy.hs b/Data/Text/Lazy.hs index 90eb571f..8246baf1 100644 --- a/Data/Text/Lazy.hs +++ b/Data/Text/Lazy.hs @@ -1,11 +1,8 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} -{-# LANGUAGE BangPatterns, MagicHash, CPP #-} +{-# LANGUAGE BangPatterns, MagicHash, CPP, TypeFamilies #-} #if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE Trustworthy #-} #endif -#if __GLASGOW_HASKELL__ >= 708 -{-# LANGUAGE TypeFamilies #-} -#endif -- Using TemplateHaskell in text unconditionally is unacceptable, as -- it's a GHC boot library. TemplateHaskellQuotes was added in 8.0, so -- this would seem to be a problem. However, GHC's policy of only @@ -246,7 +243,7 @@ import qualified GHC.CString as GHC #else import qualified GHC.Base as GHC #endif -#if __GLASGOW_HASKELL__ >= 708 +#if MIN_VERSION_base(4,7,0) import qualified GHC.Exts as Exts #endif import GHC.Prim (Addr#) @@ -378,7 +375,7 @@ instance Monoid Text where instance IsString Text where fromString = pack -#if __GLASGOW_HASKELL__ >= 708 +#if MIN_VERSION_base(4,7,0) -- | @since 1.2.0.0 instance Exts.IsList Text where type Item Text = Char diff --git a/text.cabal b/text.cabal index 4af7e220..fc750ee6 100644 --- a/text.cabal +++ b/text.cabal @@ -1,4 +1,4 @@ -cabal-version: >= 1.8 +cabal-version: >= 1.10 name: text version: 1.2.4.0 @@ -143,16 +143,16 @@ library Data.Text.Show build-depends: - array >= 0.3, - base >= 4.2 && < 5, - binary, - deepseq >= 1.1.0.0, - ghc-prim >= 0.2, - template-haskell + array >= 0.3 && < 0.6, + base >= 4.3 && < 5, + binary >= 0.5 && < 0.9, + deepseq >= 1.1 && < 1.5, + ghc-prim >= 0.2 && < 0.6, + template-haskell >= 2.5 && < 2.16 if flag(bytestring-builder) build-depends: bytestring >= 0.9 && < 0.10.4, - bytestring-builder >= 0.10.4.0.2 + bytestring-builder >= 0.10.4.0.2 && < 0.11 else build-depends: bytestring >= 0.10.4 && < 0.11 @@ -169,6 +169,36 @@ library cpp-options: -DINTEGER_GMP build-depends: integer-gmp >= 0.2 && < 1.1 + -- compiler specification + default-language: Haskell2010 + default-extensions: + NondecreasingIndentation + other-extensions: + BangPatterns + CPP + DeriveDataTypeable + ExistentialQuantification + ForeignFunctionInterface + GeneralizedNewtypeDeriving + MagicHash + OverloadedStrings + Rank2Types + RankNTypes + RecordWildCards + ScopedTypeVariables + TypeFamilies + UnboxedTuples + UnliftedFFITypes + + if impl(ghc >= 7.2) + other-extensions: Trustworthy + if impl(ghc >= 7.4) + other-extensions: Safe + if impl(ghc >= 8.0) + other-extensions: TemplateHaskellQuotes + else + other-extensions: TemplateHaskell + test-suite tests type: exitcode-stdio-1.0 c-sources: cbits/cbits.c @@ -274,6 +304,9 @@ test-suite tests cpp-options: -DINTEGER_GMP build-depends: integer-gmp >= 0.2 + default-language: Haskell2010 + default-extensions: NondecreasingIndentation + source-repository head type: git location: https://github.com/haskell/text -- GitLab