Repository : ssh://darcs.haskell.org//srv/darcs/packages/array

On branch  : ghc-kinds

http://hackage.haskell.org/trac/ghc/changeset/5dbb867423beaa8d1df01b68bbca9fe549a2d96e

>---------------------------------------------------------------

commit 5dbb867423beaa8d1df01b68bbca9fe549a2d96e
Author: Julien Cretin <[email protected]>
Date:   Thu Sep 22 15:00:59 2011 +0200

    kind annotations to make Arrays kind monomorphic

>---------------------------------------------------------------

 Data/Array/Base.hs |    5 +++--
 1 files changed, 3 insertions(+), 2 deletions(-)

diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs
index 9d1e0ec..b509f91 100644
--- a/Data/Array/Base.hs
+++ b/Data/Array/Base.hs
@@ -1,5 +1,6 @@
 {-# OPTIONS_GHC -XBangPatterns -fno-warn-unused-imports #-}
 {-# OPTIONS_HADDOCK hide #-}
+{-# LANGUAGE KindSignatures #-}
 -- XXX With a GHC 6.9 we get a spurious
 -- Data/Array/Base.hs:26:0:
 --     Warning: Module `Data.Ix' is imported, but nothing from it is used,
@@ -433,7 +434,7 @@ instance IArray Arr.Array e where
 -- "Data.Array.Unboxed" instead of "Data.Array").
 --
 #ifdef __GLASGOW_HASKELL__
-data UArray i e = UArray !i !i !Int ByteArray#
+data UArray i (e :: *) = UArray !i !i !Int ByteArray#
 #endif
 #ifdef __HUGS__
 data UArray i e = UArray !i !i !Int !ByteArray
@@ -1128,7 +1129,7 @@ INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
 -- don\'t use 'STUArray' if you require the non-strictness that
 -- 'STArray' provides.
 #ifdef __GLASGOW_HASKELL__
-data STUArray s i e = STUArray !i !i !Int (MutableByteArray# s)
+data STUArray s i (e :: *) = STUArray !i !i !Int (MutableByteArray# s)
 #endif
 #ifdef __HUGS__
 data STUArray s i e = STUArray !i !i !Int !(MutableByteArray s)



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to