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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/04c0cd1166d0493f67a0ac716a0679f64e154c1e

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

commit 04c0cd1166d0493f67a0ac716a0679f64e154c1e
Author: Roman Leshchinskiy <[email protected]>
Date:   Thu Dec 29 11:16:17 2011 +0000

    Remove dead code

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

 Data/Vector/Internal/Check.hs |    9 +--------
 include/vector.h              |    8 --------
 2 files changed, 1 insertions(+), 16 deletions(-)

diff --git a/Data/Vector/Internal/Check.hs b/Data/Vector/Internal/Check.hs
index 948e46b..2205ade 100644
--- a/Data/Vector/Internal/Check.hs
+++ b/Data/Vector/Internal/Check.hs
@@ -16,7 +16,7 @@ module Data.Vector.Internal.Check (
   Checks(..), doChecks,
 
   error, emptyStream,
-  check, assert, checkIndex, checkLength, checkSlice
+  check, checkIndex, checkLength, checkSlice
 ) where
 
 import GHC.Base( Int(..) )
@@ -74,13 +74,6 @@ check file line kind loc msg cond x
   | not (doChecks kind) || cond = x
   | otherwise = error file line kind loc msg
 
-assert_msg :: String
-assert_msg = "assertion failure"
-
-assert :: String -> Int -> Checks -> String -> Bool -> a -> a
-{-# INLINE assert #-}
-assert file line kind loc = check file line kind loc assert_msg
-
 checkIndex_msg :: Int -> Int -> String
 {-# INLINE checkIndex_msg #-}
 checkIndex_msg (I# i#) (I# n#) = checkIndex_msg# i# n#
diff --git a/include/vector.h b/include/vector.h
index a8666c5..a04bc0b 100644
--- a/include/vector.h
+++ b/include/vector.h
@@ -9,23 +9,15 @@ import qualified Data.Vector.Internal.Check as Ck
 #endif
 
 #define ERROR(f)  (Ck.f __FILE__ __LINE__)
-#define ASSERT (Ck.assert __FILE__ __LINE__)
-#define ENSURE (Ck.f __FILE__ __LINE__)
 #define CHECK(f) (Ck.f __FILE__ __LINE__)
 
 #define BOUNDS_ERROR(f) (ERROR(f) Ck.Bounds)
-#define BOUNDS_ASSERT (ASSERT Ck.Bounds)
-#define BOUNDS_ENSURE (ENSURE Ck.Bounds)
 #define BOUNDS_CHECK(f) (CHECK(f) Ck.Bounds)
 
 #define UNSAFE_ERROR(f) (ERROR(f) Ck.Unsafe)
-#define UNSAFE_ASSERT (ASSERT Ck.Unsafe)
-#define UNSAFE_ENSURE (ENSURE Ck.Unsafe)
 #define UNSAFE_CHECK(f) (CHECK(f) Ck.Unsafe)
 
 #define INTERNAL_ERROR(f) (ERROR(f) Ck.Internal)
-#define INTERNAL_ASSERT (ASSERT Ck.Internal)
-#define INTERNAL_ENSURE (ENSURE Ck.Internal)
 #define INTERNAL_CHECK(f) (CHECK(f) Ck.Internal)
 
 



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

Reply via email to