[commit: packages/bytestring] ghc-head: Declare all extensions in .hs files (f2b3258)
git at git.haskell.org
git
Thu Oct 10 08:56:21 UTC 2013
Repository : ssh://git at git.haskell.org/bytestring
On branch : ghc-head
Link : http://git.haskell.org/packages/bytestring.git/commitdiff/f2b3258d80f268a8ddc6d386c896d820ac334603
>---------------------------------------------------------------
commit f2b3258d80f268a8ddc6d386c896d820ac334603
Author: Duncan Coutts <duncan at community.haskell.org>
Date: Sun Oct 6 14:55:48 2013 +0100
Declare all extensions in .hs files
Use Cabal-1.10 feature of other-extensions, so we declare which
extensions are used, but don't just apply all extensions to all
modules.
>---------------------------------------------------------------
f2b3258d80f268a8ddc6d386c896d820ac334603
Data/ByteString/Builder/ASCII.hs | 3 ++-
Data/ByteString/Builder/Internal.hs | 2 +-
Data/ByteString/Short/Internal.hs | 3 ++-
bench/bench-bytestring.cabal | 17 ++++-----------
bytestring.cabal | 40 ++++++++++++++++++-----------------
tests/builder/TestSuite.hs | 1 +
6 files changed, 31 insertions(+), 35 deletions(-)
diff --git a/Data/ByteString/Builder/ASCII.hs b/Data/ByteString/Builder/ASCII.hs
index 881f466..ffd2ad7 100644
--- a/Data/ByteString/Builder/ASCII.hs
+++ b/Data/ByteString/Builder/ASCII.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE ScopedTypeVariables, CPP, ForeignFunctionInterface #-}
+{-# LANGUAGE ScopedTypeVariables, CPP, ForeignFunctionInterface,
+ MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK hide #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs
index 11cf043..e1ee141 100644
--- a/Data/ByteString/Builder/Internal.hs
+++ b/Data/ByteString/Builder/Internal.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, Rank2Types #-}
+{-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, RankNTypes #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Unsafe #-}
#endif
diff --git a/Data/ByteString/Short/Internal.hs b/Data/ByteString/Short/Internal.hs
index 4898c78..092f062 100644
--- a/Data/ByteString/Short/Internal.hs
+++ b/Data/ByteString/Short/Internal.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE DeriveDataTypeable, CPP, BangPatterns, RankNTypes,
- ForeignFunctionInterface, MagicHash, UnboxedTuples #-}
+ ForeignFunctionInterface, MagicHash, UnboxedTuples,
+ UnliftedFFITypes #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Unsafe #-}
diff --git a/bench/bench-bytestring.cabal b/bench/bench-bytestring.cabal
index 3222a3c..6421301 100644
--- a/bench/bench-bytestring.cabal
+++ b/bench/bench-bytestring.cabal
@@ -19,7 +19,7 @@ Bug-reports: iridcode at gmail.com
duncan at community.haskell.org
Tested-With: GHC==7.0.3
Build-Type: Simple
-Cabal-Version: >= 1.8
+Cabal-Version: >= 1.10
source-repository head
type: darcs
@@ -51,6 +51,7 @@ executable bench-bytestring-builder
includes: fpstring.h
install-includes: fpstring.h
+ default-language: Haskell98
ghc-options: -O2
-fmax-simplifier-iterations=10
-fdicts-cheap
@@ -66,18 +67,6 @@ executable bench-bytestring-builder
cpp-options: -DINTEGER_GMP
build-depends: integer >= 0.1 && < 0.2
-
- if impl(ghc)
- extensions: UnliftedFFITypes,
- MagicHash,
- UnboxedTuples,
- DeriveDataTypeable
- ScopedTypeVariables
- Rank2Types
- NamedFieldPuns
- PackageImports
- ForeignFunctionInterface
-
-- executable bench-float-decimal
-- hs-source-dirs: . ..
-- main-is: BenchFloatDec.hs
@@ -137,6 +126,7 @@ executable bench-builder-boundscheck
-fmax-simplifier-iterations=10
-fdicts-cheap
-fspec-constr-count=6
+ default-language: Haskell98
--executable bench-builder-csv
-- hs-source-dirs: .. .
@@ -151,4 +141,5 @@ executable bench-builder-boundscheck
-- -fmax-simplifier-iterations=10
-- -fdicts-cheap
-- -fspec-constr-count=6
+-- default-language: Haskell98
diff --git a/bytestring.cabal b/bytestring.cabal
index 75dc6c6..8fd35a2 100644
--- a/bytestring.cabal
+++ b/bytestring.cabal
@@ -57,7 +57,7 @@ Homepage: https://github.com/haskell/bytestring
Bug-reports: https://github.com/haskell/bytestring/issues
Tested-With: GHC==7.6.1, GHC==7.4.1, GHC==7.0.4, GHC==6.12.3
Build-Type: Simple
-Cabal-Version: >= 1.8
+Cabal-Version: >= 1.10
extra-source-files: README TODO
source-repository head
@@ -102,7 +102,8 @@ library
Data.ByteString.Builder.Prim.Internal.UncheckedShifts
Data.ByteString.Builder.Prim.Internal.Base16
- extensions: CPP,
+ default-language: Haskell98
+ other-extensions: CPP,
ForeignFunctionInterface,
BangPatterns
UnliftedFFITypes,
@@ -110,8 +111,13 @@ library
UnboxedTuples,
DeriveDataTypeable
ScopedTypeVariables
- Rank2Types
+ RankNTypes
NamedFieldPuns
+ -- older ghc had issues with language pragmas guarded by cpp
+ if impl(ghc < 7)
+ default-extensions: CPP, MagicHash, UnboxedTuples,
+ DeriveDataTypeable, BangPatterns,
+ NamedFieldPuns
ghc-options: -Wall
-O2
@@ -150,13 +156,12 @@ test-suite prop-compiled
include-dirs: include
ghc-options: -fwarn-unused-binds
-fno-enable-rewrite-rules
- extensions: BangPatterns
- UnliftedFFITypes,
- MagicHash,
- UnboxedTuples,
- DeriveDataTypeable
- ScopedTypeVariables
- NamedFieldPuns
+ default-language: Haskell98
+ -- older ghc had issues with language pragmas guarded by cpp
+ if impl(ghc < 7)
+ default-extensions: CPP, MagicHash, UnboxedTuples,
+ DeriveDataTypeable, BangPatterns,
+ NamedFieldPuns
test-suite test-builder
type: exitcode-stdio-1.0
@@ -177,15 +182,12 @@ test-suite test-builder
ghc-options: -Wall -fwarn-tabs
- extensions: CPP, ForeignFunctionInterface
- UnliftedFFITypes,
- MagicHash,
- UnboxedTuples,
- DeriveDataTypeable
- ScopedTypeVariables
- Rank2Types
- BangPatterns
- NamedFieldPuns
+ default-language: Haskell98
+ -- older ghc had issues with language pragmas guarded by cpp
+ if impl(ghc < 7)
+ default-extensions: CPP, MagicHash, UnboxedTuples,
+ DeriveDataTypeable, BangPatterns,
+ NamedFieldPuns
c-sources: cbits/fpstring.c
cbits/itoa.c
diff --git a/tests/builder/TestSuite.hs b/tests/builder/TestSuite.hs
index 5378ee3..2c76fbd 100644
--- a/tests/builder/TestSuite.hs
+++ b/tests/builder/TestSuite.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module Main where
import qualified Data.ByteString.Builder.Tests
More information about the ghc-commits
mailing list