diff --git a/Data/Text.hs b/Data/Text.hs index ce953f0e3f73dcff1e784c84555011ad5a01fbd5..3e6693b3d0098bc4ff3d8c79dec38bed3947fc03 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 849c6338b06663bed196b43864bbc0e1de47b511..cf5cb8cbc0a9794d89fcd3cf50a751b60501553f 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 fd0f1e42d061a478620013950678c2fb7a16cb35..d89367960db56472ac91873f9bdd5d86a89c9346 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 0dad97e1cc6ae40f94986b9a60b619ab632978e8..2e9feab6b7e5ca688c0450c2a1723ec46247ca61 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 f002ccc03bb65e57c4f236ca87ad1729d4aee3b4..2973b1e326b3a3aef8db4574a148efd02edae5c3 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 260dd3f44cb067f75735dc40ae15dbcb6aece984..a80086372b163e78fc896d5889a4d4d86e3d2ddd 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 00cf699977e42267b215a5df86af6aa9b46fc7ef..50118c97d37b67fe259e2e948a72d27f5ca03a69 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 1cf9096118d199621932e34a41300edf88bd7c2e..8a26f87b439aabb4f7052e2e9d7330e848e785ad 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 90eb571f837880a273e759a48bd90152f90a59bd..8246baf1ee4cea773b5c6d918cedc5c84f349d14 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 4af7e2205e2d2509d3116a27c0a9de25b54494b7..fc750ee6680d2e312db8a0ba338decd45e603ec8 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