Repository : ssh://darcs.haskell.org//srv/darcs/packages/vector On branch : master
http://hackage.haskell.org/trac/ghc/changeset/a08a0568db5897323d163e0fbfb29767536ed09b >--------------------------------------------------------------- commit a08a0568db5897323d163e0fbfb29767536ed09b Author: Roman Leshchinskiy <[email protected]> Date: Fri Aug 26 23:07:56 2011 +0000 Change comments in Safe modules >--------------------------------------------------------------- Data/Vector/Fusion/Stream/Monadic/Safe.hs | 4 +--- Data/Vector/Fusion/Stream/Safe.hs | 4 +--- Data/Vector/Generic/Mutable/Safe.hs | 4 +--- Data/Vector/Generic/New/Safe.hs | 4 +--- Data/Vector/Generic/Safe.hs | 4 +--- Data/Vector/Mutable/Safe.hs | 4 +--- Data/Vector/Primitive/Mutable/Safe.hs | 4 +--- Data/Vector/Primitive/Safe.hs | 5 +---- Data/Vector/Safe.hs | 14 +------------- Data/Vector/Unboxed/Mutable/Safe.hs | 4 +--- Data/Vector/Unboxed/Safe.hs | 27 +-------------------------- 11 files changed, 11 insertions(+), 67 deletions(-) diff --git a/Data/Vector/Fusion/Stream/Monadic/Safe.hs b/Data/Vector/Fusion/Stream/Monadic/Safe.hs index 2e2a4c9..1805dc5 100644 --- a/Data/Vector/Fusion/Stream/Monadic/Safe.hs +++ b/Data/Vector/Fusion/Stream/Monadic/Safe.hs @@ -11,9 +11,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Monadic stream combinators. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Fusion.Stream.Monadic" -- module Data.Vector.Fusion.Stream.Monadic.Safe ( diff --git a/Data/Vector/Fusion/Stream/Safe.hs b/Data/Vector/Fusion/Stream/Safe.hs index 95160e4..00ac9c2 100644 --- a/Data/Vector/Fusion/Stream/Safe.hs +++ b/Data/Vector/Fusion/Stream/Safe.hs @@ -11,9 +11,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Streams for stream fusion. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Fusion.Stream" -- module Data.Vector.Fusion.Stream.Safe ( diff --git a/Data/Vector/Generic/Mutable/Safe.hs b/Data/Vector/Generic/Mutable/Safe.hs index df17218..3e50edb 100644 --- a/Data/Vector/Generic/Mutable/Safe.hs +++ b/Data/Vector/Generic/Mutable/Safe.hs @@ -10,9 +10,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Generic interface to mutable vectors >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Generic.Mutable" -- module Data.Vector.Generic.Mutable.Safe ( diff --git a/Data/Vector/Generic/New/Safe.hs b/Data/Vector/Generic/New/Safe.hs index 8dd11c6..ee19809 100644 --- a/Data/Vector/Generic/New/Safe.hs +++ b/Data/Vector/Generic/New/Safe.hs @@ -11,9 +11,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Purely functional interface to initialisation of mutable vectors >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Generic.New" -- module Data.Vector.Generic.New.Safe ( diff --git a/Data/Vector/Generic/Safe.hs b/Data/Vector/Generic/Safe.hs index 7dc261f..1961b36 100644 --- a/Data/Vector/Generic/Safe.hs +++ b/Data/Vector/Generic/Safe.hs @@ -10,9 +10,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Generic interface to pure vectors. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Generic" -- module Data.Vector.Generic.Safe ( diff --git a/Data/Vector/Mutable/Safe.hs b/Data/Vector/Mutable/Safe.hs index 35620ea..3c629aa 100644 --- a/Data/Vector/Mutable/Safe.hs +++ b/Data/Vector/Mutable/Safe.hs @@ -11,9 +11,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Mutable boxed vectors. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Mutable" -- module Data.Vector.Mutable.Safe ( diff --git a/Data/Vector/Primitive/Mutable/Safe.hs b/Data/Vector/Primitive/Mutable/Safe.hs index 68c3a75..b4e3c40 100644 --- a/Data/Vector/Primitive/Mutable/Safe.hs +++ b/Data/Vector/Primitive/Mutable/Safe.hs @@ -10,9 +10,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Mutable primitive vectors. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Primitive.Mutable" -- module Data.Vector.Primitive.Mutable.Safe ( diff --git a/Data/Vector/Primitive/Safe.hs b/Data/Vector/Primitive/Safe.hs index 651cde7..3b1e4e0 100644 --- a/Data/Vector/Primitive/Safe.hs +++ b/Data/Vector/Primitive/Safe.hs @@ -11,10 +11,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Unboxed vectors of primitive types. The use of this module is not --- recommended except in very special cases. Adaptive unboxed vectors defined --- in "Data.Vector.Unboxed" are significantly more flexible at no performance --- cost. +-- Safe interface to "Data.Vector.Primitive" -- module Data.Vector.Primitive.Safe ( diff --git a/Data/Vector/Safe.hs b/Data/Vector/Safe.hs index 4dbbd69..96711b4 100644 --- a/Data/Vector/Safe.hs +++ b/Data/Vector/Safe.hs @@ -10,19 +10,7 @@ -- Stability : experimental -- Portability : non-portable -- --- A library for boxed vectors (that is, polymorphic arrays capable of --- holding any Haskell value). The vectors come in two flavors: >--------------------------------------------------------------- --- * mutable >--------------------------------------------------------------- --- * immutable >--------------------------------------------------------------- --- and support a rich interface of both list-like operations, and bulk --- array operations. >--------------------------------------------------------------- --- Safe API only. >--------------------------------------------------------------- --- For unboxed arrays, use the 'Data.Vector.Unboxed' interface. +-- Safe interface to "Data.Vector" -- module Data.Vector.Safe ( diff --git a/Data/Vector/Unboxed/Mutable/Safe.hs b/Data/Vector/Unboxed/Mutable/Safe.hs index 2fadf76..62ff2d2 100644 --- a/Data/Vector/Unboxed/Mutable/Safe.hs +++ b/Data/Vector/Unboxed/Mutable/Safe.hs @@ -10,9 +10,7 @@ -- Stability : experimental -- Portability : non-portable -- --- Mutable adaptive unboxed vectors. >--------------------------------------------------------------- --- Safe API only. +-- Safe interface to "Data.Vector.Unboxed.Mutable" -- module Data.Vector.Unboxed.Mutable.Safe ( diff --git a/Data/Vector/Unboxed/Safe.hs b/Data/Vector/Unboxed/Safe.hs index 02a5d72..7825ce8 100644 --- a/Data/Vector/Unboxed/Safe.hs +++ b/Data/Vector/Unboxed/Safe.hs @@ -11,33 +11,8 @@ -- Stability : experimental -- Portability : non-portable -- --- Adaptive unboxed vectors. The implementation is based on type families --- and picks an efficient, specialised representation for every element type. --- In particular, unboxed vectors of pairs are represented as pairs of unboxed --- vectors. +-- Safe interface to "Data.Vector.Unboxed" -- --- Safe API only. >--------------------------------------------------------------- --- Implementing unboxed vectors for new data types can be very easy. Here is --- how the library does this for 'Complex' by simply wrapping vectors of --- pairs. >--------------------------------------------------------------- --- @ --- newtype instance 'MVector' s ('Complex' a) = MV_Complex ('MVector' s (a,a)) --- newtype instance 'Vector' ('Complex' a) = V_Complex ('Vector' (a,a)) >--------------------------------------------------------------- --- instance ('RealFloat' a, 'Unbox' a) => 'Data.Vector.Generic.Mutable.MVector' 'MVector' ('Complex' a) where --- {-\# INLINE basicLength \#-} --- basicLength (MV_Complex v) = 'Data.Vector.Generic.Mutable.basicLength' v --- ... >--------------------------------------------------------------- --- instance ('RealFloat' a, 'Unbox' a) => Data.Vector.Generic.Vector 'Vector' ('Complex' a) where --- {-\# INLINE basicLength \#-} --- basicLength (V_Complex v) = Data.Vector.Generic.basicLength v --- ... >--------------------------------------------------------------- --- instance ('RealFloat' a, 'Unbox' a) => 'Unbox' ('Complex' a) --- @ module Data.Vector.Unboxed.Safe ( -- * Unboxed vectors _______________________________________________ Cvs-libraries mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-libraries
