[commit: packages/integer-gmp] master: Refactor & modernize `.cabal` to `cabal-version>=1.10` (626b563)
git at git.haskell.org
git at git.haskell.org
Thu Oct 24 13:44:55 UTC 2013
Repository : ssh://git@git.haskell.org/integer-gmp
On branch : master
Link : http://git.haskell.org/packages/integer-gmp.git/commitdiff/626b563addba0b164fb738cf98f17504dd3f62bc
>---------------------------------------------------------------
commit 626b563addba0b164fb738cf98f17504dd3f62bc
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Thu Oct 24 14:50:50 2013 +0200
Refactor & modernize `.cabal` to `cabal-version>=1.10`
This sets a sensible cabal category (i.e. `Numerical`), extends
`extra-tmp-{files,files}` to make this package self-contained, updates
the bug-report URL, and cleans up the `{-# LANGUAGE #-}` pragma usage in
the source code.
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
626b563addba0b164fb738cf98f17504dd3f62bc
GHC/Integer/GMP/Prim.hs | 5 ++--
GHC/Integer/Type.lhs | 2 +-
integer-gmp.cabal | 68 ++++++++++++++++++++++++++++++++++-------------
3 files changed, 53 insertions(+), 22 deletions(-)
diff --git a/GHC/Integer/GMP/Prim.hs b/GHC/Integer/GMP/Prim.hs
index de9477f..401855b 100644
--- a/GHC/Integer/GMP/Prim.hs
+++ b/GHC/Integer/GMP/Prim.hs
@@ -1,6 +1,5 @@
-{-# LANGUAGE ForeignFunctionInterface, GHCForeignImportPrim, CPP,
- MagicHash, UnboxedTuples, UnliftedFFITypes, BangPatterns #-}
-{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# LANGUAGE BangPatterns, CPP, MagicHash, NoImplicitPrelude, UnboxedTuples
+ , UnliftedFFITypes, GHCForeignImportPrim #-}
{-# OPTIONS_HADDOCK hide #-}
#include "MachDeps.h"
diff --git a/GHC/Integer/Type.lhs b/GHC/Integer/Type.lhs
index 3d4994a..6e13eb5 100644
--- a/GHC/Integer/Type.lhs
+++ b/GHC/Integer/Type.lhs
@@ -1,5 +1,5 @@
\begin{code}
-{-# LANGUAGE BangPatterns, CPP, MagicHash, NoImplicitPrelude #-}
+{-# LANGUAGE BangPatterns, CPP, UnboxedTuples, UnliftedFFITypes, MagicHash, NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK hide #-}
-- Commentary of Integer library is located on the wiki:
diff --git a/integer-gmp.cabal b/integer-gmp.cabal
index be9ce7e..6bc847c 100644
--- a/integer-gmp.cabal
+++ b/integer-gmp.cabal
@@ -3,35 +3,67 @@ version: 0.5.1.0
-- GHC 7.6.1 released with 0.5.0.0
license: BSD3
license-file: LICENSE
+category: Numerical
maintainer: libraries at haskell.org
-bug-reports: http://hackage.haskell.org/trac/ghc/newticket?component=libraries%20%28other%29
+bug-reports: http://ghc.haskell.org/trac/ghc/newticket?component=libraries%20%28other%29&keywords=integer-gmp
synopsis: Integer library based on GMP
description:
This package contains an Integer library based on GMP.
-cabal-version: >=1.6
-build-type: Configure
+build-type: Configure
+cabal-version: >=1.10
extra-source-files:
- cbits/float.c
- cbits/alloc.c
- cbits/longlong.c
+ aclocal.m4
+ cbits/alloc.c
+ cbits/float.c
+ cbits/gmp-wrappers.cmm
+ cbits/longlong.c
+ config.guess
+ config.sub
+ configure
+ configure.ac
+ gmp/config.mk.in
+ install-sh
+ integer-gmp.buildinfo.in
+
+extra-tmp-files:
+ autom4te.cache
+ config.log
+ config.status
source-repository head
type: git
location: http://git.haskell.org/packages/integer-gmp.git
-Library {
- build-depends: ghc-prim
- exposed-modules: GHC.Integer
- GHC.Integer.GMP.Internals
- GHC.Integer.GMP.Prim
- GHC.Integer.Logarithms
- GHC.Integer.Logarithms.Internals
- other-modules: GHC.Integer.Type
- extensions: CPP, MagicHash, UnboxedTuples, NoImplicitPrelude,
- ForeignFunctionInterface, UnliftedFFITypes
+source-repository this
+ type: git
+ location: http://git.haskell.org/packages/integer-gmp.git
+ tag: integer-gmp-0.5.1.0-release
+
+Library
+ default-language: Haskell2010
+ other-extensions:
+ BangPatterns
+ CPP
+ GHCForeignImportPrim
+ MagicHash
+ NoImplicitPrelude
+ UnboxedTuples
+ UnliftedFFITypes
+
+ exposed-modules:
+ GHC.Integer
+ GHC.Integer.GMP.Internals
+ GHC.Integer.GMP.Prim
+ GHC.Integer.Logarithms
+ GHC.Integer.Logarithms.Internals
+ other-modules:
+ GHC.Integer.Type
+
c-sources: cbits/cbits.c
+
+ build-depends: ghc-prim >= 0.3.1 && < 0.4
+
-- We need to set the package name to integer-gmp
-- (without a version number) as it's magic.
- ghc-options: -package-name integer-gmp
-}
+ ghc-options: -Wall -package-name integer-gmp
More information about the ghc-commits
mailing list