Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
  • ghc/packages/array
  • RyanGlScott/array
  • int-index/array
  • osa1/array
  • Haskell-mouse/array
  • trac-runeks/array
  • Jdoc82/array
  • meooow/array
  • supersven/array
  • konsumlamm/array
  • tbidne/array
  • wavewave/array
12 results
Show changes
Commits on Source (8)
......@@ -834,10 +834,9 @@ same way as for 'IArray'), and also over the type of the monad, @m@,
in which the mutable array will be manipulated.
-}
class (Monad m) => MArray a e m where
-- | Returns the bounds of the array (lowest,highest)
-- | Returns the bounds of the array (lowest,highest).
getBounds :: Ix i => a i e -> m (i,i)
-- | Returns the number of elements in the array
-- | Returns the number of elements in the array.
getNumElements :: Ix i => a i e -> m Int
-- | Builds a new array, with every element initialised to the supplied
......@@ -892,6 +891,8 @@ class (Monad m) => MArray a e m where
-- default initialisation with undefined values if we *do* know the
-- initial value and it is constant for all elements.
{-# MINIMAL getBounds, getNumElements, (newArray | unsafeNewArray_), unsafeRead, unsafeWrite #-}
instance MArray IOArray e IO where
{-# INLINE getBounds #-}
getBounds (IOArray marr) = stToIO $ getBounds marr
......@@ -913,17 +914,25 @@ newListArray (l,u) es = do
f x k i
| i == n = return ()
| otherwise = unsafeWrite marr i x >> k (i+1)
foldr f (const (return ())) es 0
foldr f (\ !_i -> return ()) es 0
-- The bang above is important for GHC for unbox the Int.
return marr
{-# INLINE newGenArray #-}
-- | Constructs a mutable array using a generator function.
-- It invokes the generator function in ascending order of the indices.
newGenArray :: (MArray a e m, Ix i) => (i,i) -> (i -> m e) -> m (a i e)
newGenArray (l,u) f = do
marr <- newArray_ (l,u)
let n = safeRangeSize (l,u)
sequence_ [ f i >>= unsafeWrite marr (safeIndex (l,u) n i) | i <- range (l,u)]
newGenArray bnds f = do
let n = safeRangeSize bnds
marr <- unsafeNewArray_ bnds
let g ix k i
| i == n = return ()
| otherwise = do
x <- f ix
unsafeWrite marr i x
k (i+1)
foldr g (\ !_i -> return ()) (range bnds) 0
-- The bang above is important for GHC for unbox the Int.
return marr
{-# INLINE readArray #-}
......@@ -945,7 +954,7 @@ writeArray marr i e = do
{-# INLINE modifyArray #-}
-- | Modify an element in a mutable array
--
-- @since FIXME
-- @since 0.5.6.0
modifyArray :: (MArray a e m, Ix i) => a i e -> i -> (e -> e) -> m ()
modifyArray marr i f = do
(l,u) <- getBounds marr
......@@ -957,7 +966,7 @@ modifyArray marr i f = do
{-# INLINE modifyArray' #-}
-- | Modify an element in a mutable array. Strict in the written element.
--
-- @since FIXME
-- @since 0.5.6.0
modifyArray' :: (MArray a e m, Ix i) => a i e -> i -> (e -> e) -> m ()
modifyArray' marr i f = do
(l,u) <- getBounds marr
......
{-# LANGUAGE MagicHash, UnliftedFFITypes #-}
{-# LANGUAGE MagicHash, Trustworthy, UnliftedFFITypes #-}
-----------------------------------------------------------------------------
-- |
......
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
......
{-# LANGUAGE CPP #-}
{-# LANGUAGE CPP, Trustworthy #-}
-----------------------------------------------------------------------------
-- |
......
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RankNTypes, Trustworthy #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Array.ST
......
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Array.ST.Safe
......
{-# LANGUAGE Trustworthy #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Array.Storable
......
......@@ -2,12 +2,13 @@
#include "MachDeps.h"
import Control.Exception
import Data.Array.MArray
import Data.Array.IO
import Data.Word
main :: IO ()
main = do
main = handle (\(exc :: SomeException) -> print exc) $ do
-- This should fail due to integer overflow
#if WORD_SIZE_IN_BITS == 64
m <- newArray_ (0,2^62-1) :: IO (IOUArray Int Word32) -- allocates 0 bytes
......
T229: Data.Array.Base.safe_scale: Overflow; scale: 4, n: 1073741824
CallStack (from HasCallStack):
error, called at libraries/array/Data/Array/Base.hs:1356:20 in array-0.5.1.2:Data.Array.Base
T229: Data.Array.Base.safe_scale: Overflow; scale: 4, n: 4611686018427387904
CallStack (from HasCallStack):
error, called at libraries/array/Data/Array/Base.hs:1356:20 in array-0.5.1.2:Data.Array.Base
Data.Array.Base.safe_scale: Overflow; scale: 4, n: 1073741824
CallStack (from HasCallStack):
error, called at libraries/array/Data/Array/Base.hs:1418:20 in array-0.5.6.0-inplace:Data.Array.Base
Data.Array.Base.safe_scale: Overflow; scale: 4, n: 4611686018427387904
CallStack (from HasCallStack):
error, called at libraries/array/Data/Array/Base.hs:1418:20 in array-0.5.6.0-inplace:Data.Array.Base
......@@ -6,4 +6,4 @@ test('array001', [
compile_and_run, [''])
test('T9220', filter_stdout_lines('.*type role .*'), ghci_script, ['T9220.script'])
test('T229', [exit_code(1)], compile_and_run, [''])
test('T229', normal, compile_and_run, [''])