[commit: packages/primitive] ghc-head: Modernize `primitive.cabal` (3ae9ffb)
git at git.haskell.org
git at git.haskell.org
Thu Sep 26 11:45:14 CEST 2013
Repository : ssh://git@git.haskell.org/primitive
On branch : ghc-head
Link : http://git.haskell.org/packages/primitive.git/commitdiff/3ae9ffb14d3d9855f60506523972b1e6e4eebab8
>---------------------------------------------------------------
commit 3ae9ffb14d3d9855f60506523972b1e6e4eebab8
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Thu Sep 26 10:21:08 2013 +0200
Modernize `primitive.cabal`
This includes declaring all potentially used language pragmas in
`other-extensions` and declare the `CPP` in the `.hs` files instead of
using `default-extensions`.
Moreover, move the changelog entries out of the description field into a
top-level `changelog` file which is recognized by Hackage 2.
>---------------------------------------------------------------
3ae9ffb14d3d9855f60506523972b1e6e4eebab8
Control/Monad/Primitive.hs | 2 +-
Data/Primitive/Array.hs | 2 +-
Data/Primitive/ByteArray.hs | 2 +-
Data/Primitive/Internal/Compat.hs | 2 +-
Data/Primitive/MachDeps.hs | 2 +-
Data/Primitive/Types.hs | 2 +-
changelog | 9 +++++++++
primitive.cabal | 32 ++++++++++++--------------------
8 files changed, 27 insertions(+), 26 deletions(-)
diff --git a/Control/Monad/Primitive.hs b/Control/Monad/Primitive.hs
index 784f5b9..445a5c1 100644
--- a/Control/Monad/Primitive.hs
+++ b/Control/Monad/Primitive.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, TypeFamilies #-}
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples, TypeFamilies #-}
-- |
-- Module : Control.Monad.Primitive
diff --git a/Data/Primitive/Array.hs b/Data/Primitive/Array.hs
index 9e066d1..e2d9dd5 100644
--- a/Data/Primitive/Array.hs
+++ b/Data/Primitive/Array.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-}
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-}
-- |
-- Module : Data.Primitive.Array
diff --git a/Data/Primitive/ByteArray.hs b/Data/Primitive/ByteArray.hs
index 8decb04..b8a6a89 100644
--- a/Data/Primitive/ByteArray.hs
+++ b/Data/Primitive/ByteArray.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, ForeignFunctionInterface,
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples, ForeignFunctionInterface,
UnliftedFFITypes, DeriveDataTypeable #-}
-- |
diff --git a/Data/Primitive/Internal/Compat.hs b/Data/Primitive/Internal/Compat.hs
index c0d3b75..f6b8016 100644
--- a/Data/Primitive/Internal/Compat.hs
+++ b/Data/Primitive/Internal/Compat.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE CPP, MagicHash #-}
-- |
-- Module : Data.Primitive.Internal.Compat
diff --git a/Data/Primitive/MachDeps.hs b/Data/Primitive/MachDeps.hs
index c6cfc0b..d36c252 100644
--- a/Data/Primitive/MachDeps.hs
+++ b/Data/Primitive/MachDeps.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE CPP, MagicHash #-}
-- |
-- Module : Data.Primitive.MachDeps
-- Copyright : (c) Roman Leshchinskiy 2009-2012
diff --git a/Data/Primitive/Types.hs b/Data/Primitive/Types.hs
index cfe242c..68f2d52 100644
--- a/Data/Primitive/Types.hs
+++ b/Data/Primitive/Types.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE UnboxedTuples, MagicHash, DeriveDataTypeable #-}
+{-# LANGUAGE CPP, UnboxedTuples, MagicHash, DeriveDataTypeable #-}
-- |
-- Module : Data.Primitive.Types
diff --git a/changelog b/changelog
new file mode 100644
index 0000000..41ff6a1
--- /dev/null
+++ b/changelog
@@ -0,0 +1,9 @@
+Changes in version 0.5.0.1
+
+ * Disable array copying primitives for GHC 7.6.* and earlier
+
+Changes in version 0.5
+
+ * New in "Data.Primitive.MutVar": 'atomicModifyMutVar'
+
+ * Efficient block fill operations: 'setByteArray', 'setAddr'
diff --git a/primitive.cabal b/primitive.cabal
index 2904203..b4aa289 100644
--- a/primitive.cabal
+++ b/primitive.cabal
@@ -2,6 +2,7 @@ Name: primitive
Version: 0.5.1.0
License: BSD3
License-File: LICENSE
+
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Maintainer: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Copyright: (c) Roman Leshchinskiy 2009-2012
@@ -9,26 +10,18 @@ Homepage: https://github.com/haskell/primitive
Bug-Reports: https://github.com/haskell/primitive/issues
Category: Data
Synopsis: Primitive memory-related operations
-Description:
- .
- This package provides various primitive memory-related operations.
- .
- Changes in version 0.5.0.1
- .
- * Disable array copying primitives for GHC 7.6.* and earlier
- .
- Changes in version 0.5
- .
- * New in "Data.Primitive.MutVar": @atomicModifyMutVar@
- .
- * Efficient block fill operations: @setByteArray@, @setAddr@
- .
-
-Cabal-Version: >= 1.6
+Cabal-Version: >= 1.10
Build-Type: Simple
+Description: This package provides various primitive memory-related operations.
+
+Extra-Source-Files: changelog
Library
- Extensions: CPP
+ Default-Language: Haskell2010
+ Other-Extensions:
+ BangPatterns, CPP, DeriveDataTypeable, ForeignFunctionInterface,
+ MagicHash, TypeFamilies, UnboxedTuples, UnliftedFFITypes
+
Exposed-Modules:
Control.Monad.Primitive
Data.Primitive
@@ -52,9 +45,8 @@ Library
includes: primitive-memops.h
c-sources: cbits/primitive-memops.c
cc-options: -O3 -ftree-vectorize -fomit-frame-pointer
- if arch(i386) || arch(x86_64) {
- cc-options: -msse2
- }
+ if arch(i386) || arch(x86_64)
+ cc-options: -msse2
source-repository head
type: git
More information about the ghc-commits
mailing list