{-# LANGUAGE
    BangPatterns
  , CPP
  , RankNTypes
  , MagicHash
  , UnboxedTuples
  , MultiParamTypeClasses
  , FlexibleInstances
  , FlexibleContexts
  , UnliftedFFITypes
  , RoleAnnotations
 #-}
{-# OPTIONS_HADDOCK hide #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Array.Base
-- Copyright   :  (c) The University of Glasgow 2001
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  non-portable (MPTCs, uses Control.Monad.ST)
--
-- Basis for IArray and MArray.  Not intended for external consumption;
-- use IArray or MArray instead.
--
-----------------------------------------------------------------------------

module Data.Array.Base where

import Control.Monad.ST.Lazy ( strictToLazyST )
import qualified Control.Monad.ST.Lazy as Lazy (ST)
import Data.Ix ( Ix, range, index, rangeSize )
import Foreign.C.Types
import Foreign.StablePtr

import Data.Char
import GHC.Arr          ( STArray )
import qualified GHC.Arr as Arr
import qualified GHC.Arr as ArrST
import GHC.ST           ( ST(..), runST )
import GHC.Base         ( IO(..), divInt# )
import GHC.Exts
import GHC.Ptr          ( nullPtr, nullFunPtr )
import GHC.Show         ( appPrec )
import GHC.Stable       ( StablePtr(..) )
import GHC.Read         ( expectP, parens, Read(..) )
import GHC.Int          ( Int8(..),  Int16(..),  Int32(..),  Int64(..) )
import GHC.Word         ( Word8(..), Word16(..), Word32(..), Word64(..) )
import GHC.IO           ( stToIO )
import GHC.IOArray      ( IOArray(..),
                          newIOArray, unsafeReadIOArray, unsafeWriteIOArray )
import Text.Read.Lex    ( Lexeme(Ident) )
import Text.ParserCombinators.ReadPrec ( prec, ReadPrec, step )

#include "MachDeps.h"

-----------------------------------------------------------------------------
-- Class of immutable arrays

{- | Class of immutable array types.

An array type has the form @(a i e)@ where @a@ is the array type
constructor (kind @* -> * -> *@), @i@ is the index type (a member of
the class 'Ix'), and @e@ is the element type.  The @IArray@ class is
parameterised over both @a@ and @e@, so that instances specialised to
certain element types can be defined.
-}
class IArray a e where
    -- | Extracts the bounds of an immutable array
    bounds           :: Ix i => a i e -> (i,i)
    numElements      :: Ix i => a i e -> Int
    unsafeArray      :: Ix i => (i,i) -> [(Int, e)] -> a i e
    unsafeAt         :: Ix i => a i e -> Int -> e
    unsafeReplace    :: Ix i => a i e -> [(Int, e)] -> a i e
    unsafeAccum      :: Ix i => (e -> e' -> e) -> a i e -> [(Int, e')] -> a i e
    unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i,i) -> [(Int, e')] -> a i e

    unsafeReplace a i e
arr [(Int, e)]
ies = (forall s. ST s (a i e)) -> a i e
forall a. (forall s. ST s a) -> a
runST (a i e -> [(Int, e)] -> ST s (STArray s i e)
forall (a :: * -> * -> *) e i s.
(IArray a e, Ix i) =>
a i e -> [(Int, e)] -> ST s (STArray s i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeReplaceST a i e
arr [(Int, e)]
ies ST s (STArray s i e)
-> (STArray s i e -> ST s (a i e)) -> ST s (a i e)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall s. Monad (ST s)
>>= STArray s i e -> ST s (a i e)
forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
Evidence bound by a type signature of the constraint type IArray a e
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
Evidence bound by a type signature of the constraint type Ix i
unsafeFreeze)
    unsafeAccum e -> e' -> e
f a i e
arr [(Int, e')]
ies = (forall s. ST s (a i e)) -> a i e
forall a. (forall s. ST s a) -> a
runST ((e -> e' -> e) -> a i e -> [(Int, e')] -> ST s (STArray s i e)
forall (a :: * -> * -> *) e i e' s.
(IArray a e, Ix i) =>
(e -> e' -> e) -> a i e -> [(Int, e')] -> ST s (STArray s i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAccumST e -> e' -> e
f a i e
arr [(Int, e')]
ies ST s (STArray s i e)
-> (STArray s i e -> ST s (a i e)) -> ST s (a i e)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall s. Monad (ST s)
>>= STArray s i e -> ST s (a i e)
forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
Evidence bound by a type signature of the constraint type IArray a e
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
Evidence bound by a type signature of the constraint type Ix i
unsafeFreeze)
    unsafeAccumArray e -> e' -> e
f e
e (i, i)
lu [(Int, e')]
ies = (forall s. ST s (a i e)) -> a i e
forall a. (forall s. ST s a) -> a
runST ((e -> e' -> e)
-> e -> (i, i) -> [(Int, e')] -> ST s (STArray s i e)
forall i e e' s.
Ix i =>
(e -> e' -> e)
-> e -> (i, i) -> [(Int, e')] -> ST s (STArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeAccumArrayST e -> e' -> e
f e
e (i, i)
lu [(Int, e')]
ies ST s (STArray s i e)
-> (STArray s i e -> ST s (a i e)) -> ST s (a i e)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall s. Monad (ST s)
>>= STArray s i e -> ST s (a i e)
forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
Evidence bound by a type signature of the constraint type IArray a e
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
Evidence bound by a type signature of the constraint type Ix i
unsafeFreeze)

{-# INLINE safeRangeSize #-}
safeRangeSize :: Ix i => (i, i) -> Int
safeRangeSize :: (i, i) -> Int
safeRangeSize (i
l,i
u) = let r :: Int
r = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
rangeSize (i
l, i
u)
                      in if Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 then [Char] -> Int
forall a. HasCallStack => [Char] -> a
error [Char]
"Negative range size"
                                  else Int
r

{-# INLINE safeIndex #-}
safeIndex :: Ix i => (i, i) -> Int -> i -> Int
safeIndex :: (i, i) -> Int -> i -> Int
safeIndex (i
l,i
u) Int
n i
i = let i' :: Int
i' = (i, i) -> i -> Int
forall a. Ix a => (a, a) -> a -> Int
Evidence bound by a type signature of the constraint type Ix i
index (i
l,i
u) i
i
                      in if (Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
i') Bool -> Bool -> Bool
&& (Int
i' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
n)
                         then Int
i'
                         else [Char] -> Int
forall a. HasCallStack => [Char] -> a
error ([Char]
"Error in array index; " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show Int
i' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
                                     [Char]
" not in range [0.." [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show Int
n [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")")

{-# INLINE unsafeReplaceST #-}
unsafeReplaceST :: (IArray a e, Ix i) => a i e -> [(Int, e)] -> ST s (STArray s i e)
unsafeReplaceST :: a i e -> [(Int, e)] -> ST s (STArray s i e)
unsafeReplaceST a i e
arr [(Int, e)]
ies = do
    STArray s i e
marr <- a i e -> ST s (STArray s i e)
forall i (a :: * -> * -> *) e (b :: * -> * -> *) (m :: * -> *).
(Ix i, IArray a e, MArray b e m) =>
a i e -> m (b i e)
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
Evidence bound by a type signature of the constraint type IArray a e
Evidence bound by a type signature of the constraint type Ix i
thaw a i e
arr
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
External instance of the constraint type forall s. Monad (ST s)
External instance of the constraint type Foldable []
sequence_ [STArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
unsafeWrite STArray s i e
marr Int
i e
e | (Int
i, e
e) <- [(Int, e)]
ies]
    STArray s i e -> ST s (STArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return STArray s i e
marr

{-# INLINE unsafeAccumST #-}
unsafeAccumST :: (IArray a e, Ix i) => (e -> e' -> e) -> a i e -> [(Int, e')] -> ST s (STArray s i e)
unsafeAccumST :: (e -> e' -> e) -> a i e -> [(Int, e')] -> ST s (STArray s i e)
unsafeAccumST e -> e' -> e
f a i e
arr [(Int, e')]
ies = do
    STArray s i e
marr <- a i e -> ST s (STArray s i e)
forall i (a :: * -> * -> *) e (b :: * -> * -> *) (m :: * -> *).
(Ix i, IArray a e, MArray b e m) =>
a i e -> m (b i e)
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
Evidence bound by a type signature of the constraint type IArray a e
Evidence bound by a type signature of the constraint type Ix i
thaw a i e
arr
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
External instance of the constraint type forall s. Monad (ST s)
External instance of the constraint type Foldable []
sequence_ [do e
old <- STArray s i e -> Int -> ST s e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
unsafeRead STArray s i e
marr Int
i
                  STArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
unsafeWrite STArray s i e
marr Int
i (e -> e' -> e
f e
old e'
new)
              | (Int
i, e'
new) <- [(Int, e')]
ies]
    STArray s i e -> ST s (STArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return STArray s i e
marr

{-# INLINE unsafeAccumArrayST #-}
unsafeAccumArrayST :: Ix i => (e -> e' -> e) -> e -> (i,i) -> [(Int, e')] -> ST s (STArray s i e)
unsafeAccumArrayST :: (e -> e' -> e)
-> e -> (i, i) -> [(Int, e')] -> ST s (STArray s i e)
unsafeAccumArrayST e -> e' -> e
f e
e (i
l,i
u) [(Int, e')]
ies = do
    STArray s i e
marr <- (i, i) -> e -> ST s (STArray s i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
newArray (i
l,i
u) e
e
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
External instance of the constraint type forall s. Monad (ST s)
External instance of the constraint type Foldable []
sequence_ [do e
old <- STArray s i e -> Int -> ST s e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
unsafeRead STArray s i e
marr Int
i
                  STArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
unsafeWrite STArray s i e
marr Int
i (e -> e' -> e
f e
old e'
new)
              | (Int
i, e'
new) <- [(Int, e')]
ies]
    STArray s i e -> ST s (STArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return STArray s i e
marr


{-# INLINE array #-}

{-| Constructs an immutable array from a pair of bounds and a list of
initial associations.

The bounds are specified as a pair of the lowest and highest bounds in
the array respectively.  For example, a one-origin vector of length 10
has bounds (1,10), and a one-origin 10 by 10 matrix has bounds
((1,1),(10,10)).

An association is a pair of the form @(i,x)@, which defines the value of
the array at index @i@ to be @x@.  The array is undefined if any index
in the list is out of bounds.  If any two associations in the list have
the same index, the value at that index is implementation-dependent.
(In GHC, the last value specified for that index is used.
Other implementations will also do this for unboxed arrays, but Haskell
98 requires that for 'Array' the value at such indices is bottom.)

Because the indices must be checked for these errors, 'array' is
strict in the bounds argument and in the indices of the association
list.  Whether @array@ is strict or non-strict in the elements depends
on the array type: 'Data.Array.Array' is a non-strict array type, but
all of the 'Data.Array.Unboxed.UArray' arrays are strict.  Thus in a
non-strict array, recurrences such as the following are possible:

> a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i \<- [2..100]])

Not every index within the bounds of the array need appear in the
association list, but the values associated with indices that do not
appear will be undefined.

If, in any dimension, the lower bound is greater than the upper bound,
then the array is legal, but empty. Indexing an empty array always
gives an array-bounds error, but 'bounds' still yields the bounds with
which the array was constructed.
-}
array   :: (IArray a e, Ix i)
        => (i,i)        -- ^ bounds of the array: (lowest,highest)
        -> [(i, e)]     -- ^ list of associations
        -> a i e
array :: (i, i) -> [(i, e)] -> a i e
array (i
l,i
u) [(i, e)]
ies
    = let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
      in (i, i) -> [(Int, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(Int, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeArray (i
l,i
u)
                     [((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i, e
e) | (i
i, e
e) <- [(i, e)]
ies]

-- Since unsafeFreeze is not guaranteed to be only a cast, we will
-- use unsafeArray and zip instead of a specialized loop to implement
-- listArray, unlike Array.listArray, even though it generates some
-- unnecessary heap allocation. Will use the loop only when we have
-- fast unsafeFreeze, namely for Array and UArray (well, they cover
-- almost all cases).

{-# INLINE [1] listArray #-}

-- | Constructs an immutable array from a list of initial elements.
-- The list gives the elements of the array in ascending order
-- beginning with the lowest index.
listArray :: (IArray a e, Ix i) => (i,i) -> [e] -> a i e
listArray :: (i, i) -> [e] -> a i e
listArray (i
l,i
u) [e]
es =
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
    in (i, i) -> [(Int, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(Int, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeArray (i
l,i
u) ([Int] -> [e] -> [(Int, e)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1] [e]
es)

{-# INLINE listArrayST #-}
listArrayST :: Ix i => (i,i) -> [e] -> ST s (STArray s i e)
listArrayST :: (i, i) -> [e] -> ST s (STArray s i e)
listArrayST (i
l,i
u) [e]
es = do
    STArray s i e
marr <- (i, i) -> ST s (STArray s i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
newArray_ (i
l,i
u)
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
    let fillFromList :: Int -> [e] -> m ()
fillFromList Int
i [e]
xs | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
n    = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STArray s) e m
return ()
                          | Bool
otherwise = case [e]
xs of
            []   -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STArray s) e m
return ()
            e
y:[e]
ys -> STArray s i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STArray s) e m
unsafeWrite STArray s i e
marr Int
i e
y m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STArray s) e m
>> Int -> [e] -> m ()
fillFromList (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) [e]
ys
    Int -> [e] -> ST s ()
forall {m :: * -> *}. MArray (STArray s) e m => Int -> [e] -> m ()
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
fillFromList Int
0 [e]
es
    STArray s i e -> ST s (STArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return STArray s i e
marr

{-# RULES
"listArray/Array" listArray =
    \lu es -> runST (listArrayST lu es >>= ArrST.unsafeFreezeSTArray)
    #-}

{-# INLINE listUArrayST #-}
listUArrayST :: (MArray (STUArray s) e (ST s), Ix i)
             => (i,i) -> [e] -> ST s (STUArray s i e)
listUArrayST :: (i, i) -> [e] -> ST s (STUArray s i e)
listUArrayST (i
l,i
u) [e]
es = do
    STUArray s i e
marr <- (i, i) -> ST s (STUArray s i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
newArray_ (i
l,i
u)
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
    let fillFromList :: Int -> [e] -> m ()
fillFromList Int
i [e]
xs | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
n    = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e m
return ()
                          | Bool
otherwise = case [e]
xs of
            []   -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e m
return ()
            e
y:[e]
ys -> STUArray s i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e m
unsafeWrite STUArray s i e
marr Int
i e
y m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e m
>> Int -> [e] -> m ()
fillFromList (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) [e]
ys
    Int -> [e] -> ST s ()
forall {m :: * -> *}. MArray (STUArray s) e m => Int -> [e] -> m ()
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
fillFromList Int
0 [e]
es
    STUArray s i e -> ST s (STUArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
return STUArray s i e
marr

-- I don't know how to write a single rule for listUArrayST, because
-- the type looks like constrained over 's', which runST doesn't
-- like. In fact all MArray (STUArray s) instances are polymorphic
-- wrt. 's', but runST can't know that.
--
-- More precisely, we'd like to write this:
--   listUArray :: (forall s. MArray (STUArray s) e (ST s), Ix i)
--              => (i,i) -> [e] -> UArray i e
--   listUArray lu = runST (listUArrayST lu es >>= unsafeFreezeSTUArray)
--   {-# RULES listArray = listUArray
-- Then we could call listUArray at any type 'e' that had a suitable
-- MArray instance.  But sadly we can't, because we don't have quantified
-- constraints.  Hence the mass of rules below.

-- I would like also to write a rule for listUArrayST (or listArray or
-- whatever) applied to unpackCString#. Unfortunately unpackCString#
-- calls seem to be floated out, then floated back into the middle
-- of listUArrayST, so I was not able to do this.

type ListUArray e = forall i . Ix i => (i,i) -> [e] -> UArray i e

{-# RULES
"listArray/UArray/Bool"      listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Bool
"listArray/UArray/Char"      listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Char
"listArray/UArray/Int"       listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Int
"listArray/UArray/Word"      listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Word
"listArray/UArray/Ptr"       listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray (Ptr a)
"listArray/UArray/FunPtr"    listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray (FunPtr a)
"listArray/UArray/Float"     listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Float
"listArray/UArray/Double"    listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Double
"listArray/UArray/StablePtr" listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray (StablePtr a)
"listArray/UArray/Int8"      listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Int8
"listArray/UArray/Int16"     listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Int16
"listArray/UArray/Int32"     listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Int32
"listArray/UArray/Int64"     listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Int64
"listArray/UArray/Word8"     listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Word8
"listArray/UArray/Word16"    listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Word16
"listArray/UArray/Word32"    listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Word32
"listArray/UArray/Word64"    listArray
   = (\lu es -> runST (listUArrayST lu es >>= unsafeFreezeSTUArray)) :: ListUArray Word64
    #-}

{-# INLINE (!) #-}
-- | Returns the element of an immutable array at the specified index.
(!) :: (IArray a e, Ix i) => a i e -> i -> e
! :: a i e -> i -> e
(!) a i e
arr i
i = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of
              (i
l,i
u) -> a i e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAt a i e
arr (Int -> e) -> Int -> e
forall a b. (a -> b) -> a -> b
$ (i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) (a i e -> Int
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
numElements a i e
arr) i
i

{-# INLINE indices #-}
-- | Returns a list of all the valid indices in an array.
indices :: (IArray a e, Ix i) => a i e -> [i]
indices :: a i e -> [i]
indices a i e
arr = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of (i
l,i
u) -> (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
Evidence bound by a type signature of the constraint type Ix i
range (i
l,i
u)

{-# INLINE elems #-}
-- | Returns a list of all the elements of an array, in the same order
-- as their indices.
elems :: (IArray a e, Ix i) => a i e -> [e]
elems :: a i e -> [e]
elems a i e
arr = [a i e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAt a i e
arr Int
i | Int
i <- [Int
0 .. a i e -> Int
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
numElements a i e
arr Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]

{-# INLINE assocs #-}
-- | Returns the contents of an array as a list of associations.
assocs :: (IArray a e, Ix i) => a i e -> [(i, e)]
assocs :: a i e -> [(i, e)]
assocs a i e
arr = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of
    (i
l,i
u) -> [(i
i, a i e
arr a i e -> i -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
! i
i) | i
i <- (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
Evidence bound by a type signature of the constraint type Ix i
range (i
l,i
u)]

{-# INLINE accumArray #-}

{-|
Constructs an immutable array from a list of associations.  Unlike
'array', the same index is allowed to occur multiple times in the list
of associations; an /accumulating function/ is used to combine the
values of elements with the same index.

For example, given a list of values of some index type, hist produces
a histogram of the number of occurrences of each index within a
specified range:

> hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
> hist bnds is = accumArray (+) 0 bnds [(i, 1) | i\<-is, inRange bnds i]
-}
accumArray :: (IArray a e, Ix i)
           => (e -> e' -> e)     -- ^ An accumulating function
           -> e                  -- ^ A default element
           -> (i,i)              -- ^ The bounds of the array
           -> [(i, e')]          -- ^ List of associations
           -> a i e              -- ^ Returns: the array
accumArray :: (e -> e' -> e) -> e -> (i, i) -> [(i, e')] -> a i e
accumArray e -> e' -> e
f e
initialValue (i
l,i
u) [(i, e')]
ies =
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l, i
u)
    in (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> a i e
forall (a :: * -> * -> *) e i e'.
(IArray a e, Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAccumArray e -> e' -> e
f e
initialValue (i
l,i
u)
                        [((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i, e'
e) | (i
i, e'
e) <- [(i, e')]
ies]

{-# INLINE (//) #-}
{-|
Takes an array and a list of pairs and returns an array identical to
the left argument except that it has been updated by the associations
in the right argument.  For example, if m is a 1-origin, n by n matrix,
then @m\/\/[((i,i), 0) | i \<- [1..n]]@ is the same matrix, except with
the diagonal zeroed.

As with the 'array' function, if any two associations in the list have
the same index, the value at that index is implementation-dependent.
(In GHC, the last value specified for that index is used.
Other implementations will also do this for unboxed arrays, but Haskell
98 requires that for 'Array' the value at such indices is bottom.)

For most array types, this operation is O(/n/) where /n/ is the size
of the array.  However, the diffarray package provides an array type
for which this operation has complexity linear in the number of updates.
-}
(//) :: (IArray a e, Ix i) => a i e -> [(i, e)] -> a i e
a i e
arr // :: a i e -> [(i, e)] -> a i e
// [(i, e)]
ies = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of
    (i
l,i
u) -> a i e -> [(Int, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(Int, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeReplace a i e
arr [ ((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) (a i e -> Int
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
numElements a i e
arr) i
i, e
e)
                               | (i
i, e
e) <- [(i, e)]
ies]

{-# INLINE accum #-}
{-|
@accum f@ takes an array and an association list and accumulates pairs
from the list into the array with the accumulating function @f@. Thus
'accumArray' can be defined using 'accum':

> accumArray f z b = accum f (array b [(i, z) | i \<- range b])
-}
accum :: (IArray a e, Ix i) => (e -> e' -> e) -> a i e -> [(i, e')] -> a i e
accum :: (e -> e' -> e) -> a i e -> [(i, e')] -> a i e
accum e -> e' -> e
f a i e
arr [(i, e')]
ies = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of
    (i
l,i
u) -> let n :: Int
n = a i e -> Int
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
numElements a i e
arr
             in (e -> e' -> e) -> a i e -> [(Int, e')] -> a i e
forall (a :: * -> * -> *) e i e'.
(IArray a e, Ix i) =>
(e -> e' -> e) -> a i e -> [(Int, e')] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAccum e -> e' -> e
f a i e
arr [((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i, e'
e) | (i
i, e'
e) <- [(i, e')]
ies]

{-# INLINE amap #-}
-- | Returns a new array derived from the original array by applying a
-- function to each of the elements.
amap :: (IArray a e', IArray a e, Ix i) => (e' -> e) -> a i e' -> a i e
amap :: (e' -> e) -> a i e' -> a i e
amap e' -> e
f a i e'
arr = case a i e' -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e'
bounds a i e'
arr of
    (i
l,i
u) -> let n :: Int
n = a i e' -> Int
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e'
numElements a i e'
arr
             in (i, i) -> [(Int, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(Int, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeArray (i
l,i
u) [ (Int
i, e' -> e
f (a i e' -> Int -> e'
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e'
unsafeAt a i e'
arr Int
i))
                                  | Int
i <- [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]

{-# INLINE ixmap #-}
-- | Returns a new array derived from the original array by applying a
-- function to each of the indices.
ixmap :: (IArray a e, Ix i, Ix j) => (i,i) -> (i -> j) -> a j e -> a i e
ixmap :: (i, i) -> (i -> j) -> a j e -> a i e
ixmap (i
l,i
u) i -> j
f a j e
arr =
    (i, i) -> [(i, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
array (i
l,i
u) [(i
i, a j e
arr a j e -> j -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
Evidence bound by a type signature of the constraint type Ix j
Evidence bound by a type signature of the constraint type IArray a e
! i -> j
f i
i) | i
i <- (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
Evidence bound by a type signature of the constraint type Ix i
range (i
l,i
u)]

-----------------------------------------------------------------------------
-- Normal polymorphic arrays

instance IArray Arr.Array e where
    {-# INLINE bounds #-}
    bounds :: Array i e -> (i, i)
bounds = Array i e -> (i, i)
forall i e. Array i e -> (i, i)
Arr.bounds
    {-# INLINE numElements #-}
    numElements :: Array i e -> Int
numElements      = Array i e -> Int
forall i e. Array i e -> Int
Arr.numElements
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, e)] -> Array i e
unsafeArray      = (i, i) -> [(Int, e)] -> Array i e
forall i e. Ix i => (i, i) -> [(Int, e)] -> Array i e
Evidence bound by a type signature of the constraint type Ix i
Arr.unsafeArray
    {-# INLINE unsafeAt #-}
    unsafeAt :: Array i e -> Int -> e
unsafeAt         = Array i e -> Int -> e
forall i e. Array i e -> Int -> e
Arr.unsafeAt
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: Array i e -> [(Int, e)] -> Array i e
unsafeReplace    = Array i e -> [(Int, e)] -> Array i e
forall i e. Array i e -> [(Int, e)] -> Array i e
Arr.unsafeReplace
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (e -> e' -> e) -> Array i e -> [(Int, e')] -> Array i e
unsafeAccum      = (e -> e' -> e) -> Array i e -> [(Int, e')] -> Array i e
forall e a i. (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
Arr.unsafeAccum
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> Array i e
unsafeAccumArray = (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> Array i e
forall i e a.
Ix i =>
(e -> a -> e) -> e -> (i, i) -> [(Int, a)] -> Array i e
Evidence bound by a type signature of the constraint type Ix i
Arr.unsafeAccumArray

-----------------------------------------------------------------------------
-- Flat unboxed arrays

-- | Arrays with unboxed elements.  Instances of 'IArray' are provided
-- for 'UArray' with certain element types ('Int', 'Float', 'Char',
-- etc.; see the 'UArray' class for a full list).
--
-- A 'UArray' will generally be more efficient (in terms of both time
-- and space) than the equivalent 'Data.Array.Array' with the same
-- element type.  However, 'UArray' is strict in its elements - so
-- don\'t use 'UArray' if you require the non-strictness that
-- 'Data.Array.Array' provides.
--
-- Because the @IArray@ interface provides operations overloaded on
-- the type of the array, it should be possible to just change the
-- array type being used by a program from say @Array@ to @UArray@ to
-- get the benefits of unboxed arrays (don\'t forget to import
-- "Data.Array.Unboxed" instead of "Data.Array").
--
data UArray i e = UArray !i !i !Int ByteArray#
-- There are class-based invariants on both parameters. See also #9220.
type role UArray nominal nominal

{-# INLINE unsafeArrayUArray #-}
unsafeArrayUArray :: (MArray (STUArray s) e (ST s), Ix i)
                  => (i,i) -> [(Int, e)] -> e -> ST s (UArray i e)
unsafeArrayUArray :: (i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
unsafeArrayUArray (i
l,i
u) [(Int, e)]
ies e
default_elem = do
    STUArray s i e
marr <- (i, i) -> e -> ST s (STUArray s i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
newArray (i
l,i
u) e
default_elem
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
External instance of the constraint type Foldable []
sequence_ [STUArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeWrite STUArray s i e
marr Int
i e
e | (Int
i, e
e) <- [(Int, e)]
ies]
    STUArray s i e -> ST s (UArray i e)
forall s i e. STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray STUArray s i e
marr

{-# INLINE unsafeFreezeSTUArray #-}
unsafeFreezeSTUArray :: STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray :: STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray (STUArray i
l i
u Int
n MutableByteArray# s
marr#) = STRep s (UArray i e) -> ST s (UArray i e)
forall s a. STRep s a -> ST s a
ST (STRep s (UArray i e) -> ST s (UArray i e))
-> STRep s (UArray i e) -> ST s (UArray i e)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
    case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
marr# State# s
s1# of { (# State# s
s2#, ByteArray#
arr# #) ->
    (# State# s
s2#, i -> i -> Int -> ByteArray# -> UArray i e
forall i e. i -> i -> Int -> ByteArray# -> UArray i e
UArray i
l i
u Int
n ByteArray#
arr# #) }

{-# INLINE unsafeReplaceUArray #-}
unsafeReplaceUArray :: (MArray (STUArray s) e (ST s), Ix i)
                    => UArray i e -> [(Int, e)] -> ST s (UArray i e)
unsafeReplaceUArray :: UArray i e -> [(Int, e)] -> ST s (UArray i e)
unsafeReplaceUArray UArray i e
arr [(Int, e)]
ies = do
    STUArray s i e
marr <- UArray i e -> ST s (STUArray s i e)
forall i e s. UArray i e -> ST s (STUArray s i e)
thawSTUArray UArray i e
arr
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
External instance of the constraint type Foldable []
sequence_ [STUArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeWrite STUArray s i e
marr Int
i e
e | (Int
i, e
e) <- [(Int, e)]
ies]
    STUArray s i e -> ST s (UArray i e)
forall s i e. STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray STUArray s i e
marr

{-# INLINE unsafeAccumUArray #-}
unsafeAccumUArray :: (MArray (STUArray s) e (ST s), Ix i)
                  => (e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
unsafeAccumUArray :: (e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
unsafeAccumUArray e -> e' -> e
f UArray i e
arr [(Int, e')]
ies = do
    STUArray s i e
marr <- UArray i e -> ST s (STUArray s i e)
forall i e s. UArray i e -> ST s (STUArray s i e)
thawSTUArray UArray i e
arr
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
External instance of the constraint type Foldable []
sequence_ [do e
old <- STUArray s i e -> Int -> ST s e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeRead STUArray s i e
marr Int
i
                  STUArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeWrite STUArray s i e
marr Int
i (e -> e' -> e
f e
old e'
new)
              | (Int
i, e'
new) <- [(Int, e')]
ies]
    STUArray s i e -> ST s (UArray i e)
forall s i e. STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray STUArray s i e
marr

{-# INLINE unsafeAccumArrayUArray #-}
unsafeAccumArrayUArray :: (MArray (STUArray s) e (ST s), Ix i)
                       => (e -> e' -> e) -> e -> (i,i) -> [(Int, e')] -> ST s (UArray i e)
unsafeAccumArrayUArray :: (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
unsafeAccumArrayUArray e -> e' -> e
f e
initialValue (i
l,i
u) [(Int, e')]
ies = do
    STUArray s i e
marr <- (i, i) -> e -> ST s (STUArray s i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
newArray (i
l,i
u) e
initialValue
    [ST s ()] -> ST s ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
External instance of the constraint type Foldable []
sequence_ [do e
old <- STUArray s i e -> Int -> ST s e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeRead STUArray s i e
marr Int
i
                  STUArray s i e -> Int -> e -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray (STUArray s) e (ST s)
unsafeWrite STUArray s i e
marr Int
i (e -> e' -> e
f e
old e'
new)
              | (Int
i, e'
new) <- [(Int, e')]
ies]
    STUArray s i e -> ST s (UArray i e)
forall s i e. STUArray s i e -> ST s (UArray i e)
unsafeFreezeSTUArray STUArray s i e
marr

{-# INLINE eqUArray #-}
eqUArray :: (IArray UArray e, Ix i, Eq e) => UArray i e -> UArray i e -> Bool
eqUArray :: UArray i e -> UArray i e -> Bool
eqUArray arr1 :: UArray i e
arr1@(UArray i
l1 i
u1 Int
n1 ByteArray#
_) arr2 :: UArray i e
arr2@(UArray i
l2 i
u2 Int
n2 ByteArray#
_) =
    if Int
n1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 then Int
n2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 else
    i
l1 i -> i -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Ord a => Eq a
External instance of the constraint type forall a. Ix a => Ord a
Evidence bound by a type signature of the constraint type Ix i
== i
l2 Bool -> Bool -> Bool
&& i
u1 i -> i -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Ord a => Eq a
External instance of the constraint type forall a. Ix a => Ord a
Evidence bound by a type signature of the constraint type Ix i
== i
u2 Bool -> Bool -> Bool
&&
    [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
External instance of the constraint type Foldable []
and [UArray i e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray UArray e
unsafeAt UArray i e
arr1 Int
i e -> e -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq e
== UArray i e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray UArray e
unsafeAt UArray i e
arr2 Int
i | Int
i <- [Int
0 .. Int
n1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]

{-# INLINE [1] cmpUArray #-}
cmpUArray :: (IArray UArray e, Ix i, Ord e) => UArray i e -> UArray i e -> Ordering
cmpUArray :: UArray i e -> UArray i e -> Ordering
cmpUArray UArray i e
arr1 UArray i e
arr2 = [(i, e)] -> [(i, e)] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type forall a. Ix a => Ord a
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type Ord e
compare (UArray i e -> [(i, e)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray UArray e
assocs UArray i e
arr1) (UArray i e -> [(i, e)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray UArray e
assocs UArray i e
arr2)

{-# INLINE cmpIntUArray #-}
cmpIntUArray :: (IArray UArray e, Ord e) => UArray Int e -> UArray Int e -> Ordering
cmpIntUArray :: UArray Int e -> UArray Int e -> Ordering
cmpIntUArray arr1 :: UArray Int e
arr1@(UArray Int
l1 Int
u1 Int
n1 ByteArray#
_) arr2 :: UArray Int e
arr2@(UArray Int
l2 Int
u2 Int
n2 ByteArray#
_) =
    if Int
n1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 then if Int
n2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 then Ordering
EQ else Ordering
LT else
    if Int
n2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 then Ordering
GT else
    case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
l1 Int
l2 of
        Ordering
EQ    -> (Int -> Ordering -> Ordering) -> Ordering -> [Int] -> Ordering
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr Int -> Ordering -> Ordering
cmp (Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
u1 Int
u2) [Int
0 .. (Int
n1 Int -> Int -> Int
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord Int
`min` Int
n2) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]
        Ordering
other -> Ordering
other
    where
    cmp :: Int -> Ordering -> Ordering
cmp Int
i Ordering
rest = case e -> e -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord e
compare (UArray Int e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
External instance of the constraint type Ix Int
Evidence bound by a type signature of the constraint type IArray UArray e
unsafeAt UArray Int e
arr1 Int
i) (UArray Int e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
External instance of the constraint type Ix Int
Evidence bound by a type signature of the constraint type IArray UArray e
unsafeAt UArray Int e
arr2 Int
i) of
        Ordering
EQ    -> Ordering
rest
        Ordering
other -> Ordering
other

{-# RULES "cmpUArray/Int" cmpUArray = cmpIntUArray #-}

-----------------------------------------------------------------------------
-- Showing and Reading IArrays

{-# SPECIALISE
    showsIArray :: (IArray UArray e, Ix i, Show i, Show e) =>
                   Int -> UArray i e -> ShowS
  #-}

showsIArray :: (IArray a e, Ix i, Show i, Show e) => Int -> a i e -> ShowS
showsIArray :: Int -> a i e -> [Char] -> [Char]
showsIArray Int
p a i e
a =
    Bool -> ([Char] -> [Char]) -> [Char] -> [Char]
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
appPrec) (([Char] -> [Char]) -> [Char] -> [Char])
-> ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
    [Char] -> [Char] -> [Char]
showString [Char]
"array " ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (i, i) -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show i
shows (a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
a) ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    Char -> [Char] -> [Char]
showChar Char
' ' ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    [(i, e)] -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show i
Evidence bound by a type signature of the constraint type Show e
shows (a i e -> [(i, e)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
assocs a i e
a)

{-# SPECIALISE
    readIArray :: (IArray UArray e, Ix i, Read i, Read e) =>
                   ReadPrec (UArray i e)
  #-}

readIArray :: (IArray a e, Ix i, Read i, Read e) => ReadPrec (a i e)
readIArray :: ReadPrec (a i e)
readIArray = ReadPrec (a i e) -> ReadPrec (a i e)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (a i e) -> ReadPrec (a i e))
-> ReadPrec (a i e) -> ReadPrec (a i e)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (a i e) -> ReadPrec (a i e)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
appPrec (ReadPrec (a i e) -> ReadPrec (a i e))
-> ReadPrec (a i e) -> ReadPrec (a i e)
forall a b. (a -> b) -> a -> b
$
               do Lexeme -> ReadPrec ()
expectP ([Char] -> Lexeme
Ident [Char]
"array")
                  (i, i)
theBounds <- ReadPrec (i, i) -> ReadPrec (i, i)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec (i, i)
forall a. Read a => ReadPrec a
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read i
readPrec
                  [(i, e)]
vals   <- ReadPrec [(i, e)] -> ReadPrec [(i, e)]
forall a. ReadPrec a -> ReadPrec a
step ReadPrec [(i, e)]
forall a. Read a => ReadPrec a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read e
readPrec
                  a i e -> ReadPrec (a i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return ((i, i) -> [(i, e)] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
array (i, i)
theBounds [(i, e)]
vals)

-----------------------------------------------------------------------------
-- Flat unboxed arrays: instances

instance IArray UArray Bool where
    {-# INLINE bounds #-}
    bounds :: UArray i Bool -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Bool -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Bool)] -> UArray i Bool
unsafeArray (i, i)
lu [(Int, Bool)]
ies = (forall s. ST s (UArray i Bool)) -> UArray i Bool
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Bool)] -> Bool -> ST s (UArray i Bool)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Bool (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Bool)]
ies Bool
False)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Bool -> Int -> Bool
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Bool
isTrue#
        ((ByteArray# -> Int# -> Word#
indexWordArray# ByteArray#
arr# (Int# -> Int#
bOOL_INDEX Int#
i#) Word# -> Word# -> Word#
`and#` Int# -> Word#
bOOL_BIT Int#
i#)
        Word# -> Word# -> Int#
`neWord#` Int# -> Word#
int2Word# Int#
0#)

    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Bool -> [(Int, Bool)] -> UArray i Bool
unsafeReplace UArray i Bool
arr [(Int, Bool)]
ies = (forall s. ST s (UArray i Bool)) -> UArray i Bool
forall a. (forall s. ST s a) -> a
runST (UArray i Bool -> [(Int, Bool)] -> ST s (UArray i Bool)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Bool (ST s)
unsafeReplaceUArray UArray i Bool
arr [(Int, Bool)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Bool -> e' -> Bool)
-> UArray i Bool -> [(Int, e')] -> UArray i Bool
unsafeAccum Bool -> e' -> Bool
f UArray i Bool
arr [(Int, e')]
ies = (forall s. ST s (UArray i Bool)) -> UArray i Bool
forall a. (forall s. ST s a) -> a
runST ((Bool -> e' -> Bool)
-> UArray i Bool -> [(Int, e')] -> ST s (UArray i Bool)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Bool (ST s)
unsafeAccumUArray Bool -> e' -> Bool
f UArray i Bool
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Bool -> e' -> Bool)
-> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool
unsafeAccumArray Bool -> e' -> Bool
f Bool
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Bool)) -> UArray i Bool
forall a. (forall s. ST s a) -> a
runST ((Bool -> e' -> Bool)
-> Bool -> (i, i) -> [(Int, e')] -> ST s (UArray i Bool)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Bool (ST s)
unsafeAccumArrayUArray Bool -> e' -> Bool
f Bool
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Char where
    {-# INLINE bounds #-}
    bounds :: UArray i Char -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Char -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Char)] -> UArray i Char
unsafeArray (i, i)
lu [(Int, Char)]
ies = (forall s. ST s (UArray i Char)) -> UArray i Char
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Char)] -> Char -> ST s (UArray i Char)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Char (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Char)]
ies Char
'\0')
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Char -> Int -> Char
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Char# -> Char
C# (ByteArray# -> Int# -> Char#
indexWideCharArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Char -> [(Int, Char)] -> UArray i Char
unsafeReplace UArray i Char
arr [(Int, Char)]
ies = (forall s. ST s (UArray i Char)) -> UArray i Char
forall a. (forall s. ST s a) -> a
runST (UArray i Char -> [(Int, Char)] -> ST s (UArray i Char)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Char (ST s)
unsafeReplaceUArray UArray i Char
arr [(Int, Char)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Char -> e' -> Char)
-> UArray i Char -> [(Int, e')] -> UArray i Char
unsafeAccum Char -> e' -> Char
f UArray i Char
arr [(Int, e')]
ies = (forall s. ST s (UArray i Char)) -> UArray i Char
forall a. (forall s. ST s a) -> a
runST ((Char -> e' -> Char)
-> UArray i Char -> [(Int, e')] -> ST s (UArray i Char)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Char (ST s)
unsafeAccumUArray Char -> e' -> Char
f UArray i Char
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Char -> e' -> Char)
-> Char -> (i, i) -> [(Int, e')] -> UArray i Char
unsafeAccumArray Char -> e' -> Char
f Char
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Char)) -> UArray i Char
forall a. (forall s. ST s a) -> a
runST ((Char -> e' -> Char)
-> Char -> (i, i) -> [(Int, e')] -> ST s (UArray i Char)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Char (ST s)
unsafeAccumArrayUArray Char -> e' -> Char
f Char
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Int where
    {-# INLINE bounds #-}
    bounds :: UArray i Int -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Int -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Int)] -> UArray i Int
unsafeArray (i, i)
lu [(Int, Int)]
ies = (forall s. ST s (UArray i Int)) -> UArray i Int
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Int)] -> Int -> ST s (UArray i Int)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Int)]
ies Int
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Int -> Int -> Int
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Int
I# (ByteArray# -> Int# -> Int#
indexIntArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Int -> [(Int, Int)] -> UArray i Int
unsafeReplace UArray i Int
arr [(Int, Int)]
ies = (forall s. ST s (UArray i Int)) -> UArray i Int
forall a. (forall s. ST s a) -> a
runST (UArray i Int -> [(Int, Int)] -> ST s (UArray i Int)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int (ST s)
unsafeReplaceUArray UArray i Int
arr [(Int, Int)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Int -> e' -> Int) -> UArray i Int -> [(Int, e')] -> UArray i Int
unsafeAccum Int -> e' -> Int
f UArray i Int
arr [(Int, e')]
ies = (forall s. ST s (UArray i Int)) -> UArray i Int
forall a. (forall s. ST s a) -> a
runST ((Int -> e' -> Int)
-> UArray i Int -> [(Int, e')] -> ST s (UArray i Int)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int (ST s)
unsafeAccumUArray Int -> e' -> Int
f UArray i Int
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Int -> e' -> Int) -> Int -> (i, i) -> [(Int, e')] -> UArray i Int
unsafeAccumArray Int -> e' -> Int
f Int
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Int)) -> UArray i Int
forall a. (forall s. ST s a) -> a
runST ((Int -> e' -> Int)
-> Int -> (i, i) -> [(Int, e')] -> ST s (UArray i Int)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int (ST s)
unsafeAccumArrayUArray Int -> e' -> Int
f Int
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Word where
    {-# INLINE bounds #-}
    bounds :: UArray i Word -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Word -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Word)] -> UArray i Word
unsafeArray (i, i)
lu [(Int, Word)]
ies = (forall s. ST s (UArray i Word)) -> UArray i Word
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Word)] -> Word -> ST s (UArray i Word)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Word)]
ies Word
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Word -> Int -> Word
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Word# -> Word
W# (ByteArray# -> Int# -> Word#
indexWordArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Word -> [(Int, Word)] -> UArray i Word
unsafeReplace UArray i Word
arr [(Int, Word)]
ies = (forall s. ST s (UArray i Word)) -> UArray i Word
forall a. (forall s. ST s a) -> a
runST (UArray i Word -> [(Int, Word)] -> ST s (UArray i Word)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word (ST s)
unsafeReplaceUArray UArray i Word
arr [(Int, Word)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Word -> e' -> Word)
-> UArray i Word -> [(Int, e')] -> UArray i Word
unsafeAccum Word -> e' -> Word
f UArray i Word
arr [(Int, e')]
ies = (forall s. ST s (UArray i Word)) -> UArray i Word
forall a. (forall s. ST s a) -> a
runST ((Word -> e' -> Word)
-> UArray i Word -> [(Int, e')] -> ST s (UArray i Word)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word (ST s)
unsafeAccumUArray Word -> e' -> Word
f UArray i Word
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Word -> e' -> Word)
-> Word -> (i, i) -> [(Int, e')] -> UArray i Word
unsafeAccumArray Word -> e' -> Word
f Word
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Word)) -> UArray i Word
forall a. (forall s. ST s a) -> a
runST ((Word -> e' -> Word)
-> Word -> (i, i) -> [(Int, e')] -> ST s (UArray i Word)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word (ST s)
unsafeAccumArrayUArray Word -> e' -> Word
f Word
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray (Ptr a) where
    {-# INLINE bounds #-}
    bounds :: UArray i (Ptr a) -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i (Ptr a) -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Ptr a)] -> UArray i (Ptr a)
unsafeArray (i, i)
lu [(Int, Ptr a)]
ies = (forall s. ST s (UArray i (Ptr a))) -> UArray i (Ptr a)
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Ptr a)] -> Ptr a -> ST s (UArray i (Ptr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (Ptr a) (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Ptr a)]
ies Ptr a
forall a. Ptr a
nullPtr)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i (Ptr a) -> Int -> Ptr a
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Int# -> Addr#
indexAddrArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i (Ptr a) -> [(Int, Ptr a)] -> UArray i (Ptr a)
unsafeReplace UArray i (Ptr a)
arr [(Int, Ptr a)]
ies = (forall s. ST s (UArray i (Ptr a))) -> UArray i (Ptr a)
forall a. (forall s. ST s a) -> a
runST (UArray i (Ptr a) -> [(Int, Ptr a)] -> ST s (UArray i (Ptr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (Ptr a) (ST s)
unsafeReplaceUArray UArray i (Ptr a)
arr [(Int, Ptr a)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Ptr a -> e' -> Ptr a)
-> UArray i (Ptr a) -> [(Int, e')] -> UArray i (Ptr a)
unsafeAccum Ptr a -> e' -> Ptr a
f UArray i (Ptr a)
arr [(Int, e')]
ies = (forall s. ST s (UArray i (Ptr a))) -> UArray i (Ptr a)
forall a. (forall s. ST s a) -> a
runST ((Ptr a -> e' -> Ptr a)
-> UArray i (Ptr a) -> [(Int, e')] -> ST s (UArray i (Ptr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (Ptr a) (ST s)
unsafeAccumUArray Ptr a -> e' -> Ptr a
f UArray i (Ptr a)
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Ptr a -> e' -> Ptr a)
-> Ptr a -> (i, i) -> [(Int, e')] -> UArray i (Ptr a)
unsafeAccumArray Ptr a -> e' -> Ptr a
f Ptr a
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i (Ptr a))) -> UArray i (Ptr a)
forall a. (forall s. ST s a) -> a
runST ((Ptr a -> e' -> Ptr a)
-> Ptr a -> (i, i) -> [(Int, e')] -> ST s (UArray i (Ptr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (Ptr a) (ST s)
unsafeAccumArrayUArray Ptr a -> e' -> Ptr a
f Ptr a
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray (FunPtr a) where
    {-# INLINE bounds #-}
    bounds :: UArray i (FunPtr a) -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i (FunPtr a) -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)
unsafeArray (i, i)
lu [(Int, FunPtr a)]
ies = (forall s. ST s (UArray i (FunPtr a))) -> UArray i (FunPtr a)
forall a. (forall s. ST s a) -> a
runST ((i, i)
-> [(Int, FunPtr a)] -> FunPtr a -> ST s (UArray i (FunPtr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (FunPtr a) (ST s)
unsafeArrayUArray (i, i)
lu [(Int, FunPtr a)]
ies FunPtr a
forall a. FunPtr a
nullFunPtr)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i (FunPtr a) -> Int -> FunPtr a
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Addr# -> FunPtr a
forall a. Addr# -> FunPtr a
FunPtr (ByteArray# -> Int# -> Addr#
indexAddrArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i (FunPtr a) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)
unsafeReplace UArray i (FunPtr a)
arr [(Int, FunPtr a)]
ies = (forall s. ST s (UArray i (FunPtr a))) -> UArray i (FunPtr a)
forall a. (forall s. ST s a) -> a
runST (UArray i (FunPtr a)
-> [(Int, FunPtr a)] -> ST s (UArray i (FunPtr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (FunPtr a) (ST s)
unsafeReplaceUArray UArray i (FunPtr a)
arr [(Int, FunPtr a)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (FunPtr a -> e' -> FunPtr a)
-> UArray i (FunPtr a) -> [(Int, e')] -> UArray i (FunPtr a)
unsafeAccum FunPtr a -> e' -> FunPtr a
f UArray i (FunPtr a)
arr [(Int, e')]
ies = (forall s. ST s (UArray i (FunPtr a))) -> UArray i (FunPtr a)
forall a. (forall s. ST s a) -> a
runST ((FunPtr a -> e' -> FunPtr a)
-> UArray i (FunPtr a) -> [(Int, e')] -> ST s (UArray i (FunPtr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (FunPtr a) (ST s)
unsafeAccumUArray FunPtr a -> e' -> FunPtr a
f UArray i (FunPtr a)
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (FunPtr a -> e' -> FunPtr a)
-> FunPtr a -> (i, i) -> [(Int, e')] -> UArray i (FunPtr a)
unsafeAccumArray FunPtr a -> e' -> FunPtr a
f FunPtr a
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i (FunPtr a))) -> UArray i (FunPtr a)
forall a. (forall s. ST s a) -> a
runST ((FunPtr a -> e' -> FunPtr a)
-> FunPtr a -> (i, i) -> [(Int, e')] -> ST s (UArray i (FunPtr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (FunPtr a) (ST s)
unsafeAccumArrayUArray FunPtr a -> e' -> FunPtr a
f FunPtr a
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Float where
    {-# INLINE bounds #-}
    bounds :: UArray i Float -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Float -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Float)] -> UArray i Float
unsafeArray (i, i)
lu [(Int, Float)]
ies = (forall s. ST s (UArray i Float)) -> UArray i Float
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Float)] -> Float -> ST s (UArray i Float)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Float (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Float)]
ies Float
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Float -> Int -> Float
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Float# -> Float
F# (ByteArray# -> Int# -> Float#
indexFloatArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Float -> [(Int, Float)] -> UArray i Float
unsafeReplace UArray i Float
arr [(Int, Float)]
ies = (forall s. ST s (UArray i Float)) -> UArray i Float
forall a. (forall s. ST s a) -> a
runST (UArray i Float -> [(Int, Float)] -> ST s (UArray i Float)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Float (ST s)
unsafeReplaceUArray UArray i Float
arr [(Int, Float)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Float -> e' -> Float)
-> UArray i Float -> [(Int, e')] -> UArray i Float
unsafeAccum Float -> e' -> Float
f UArray i Float
arr [(Int, e')]
ies = (forall s. ST s (UArray i Float)) -> UArray i Float
forall a. (forall s. ST s a) -> a
runST ((Float -> e' -> Float)
-> UArray i Float -> [(Int, e')] -> ST s (UArray i Float)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Float (ST s)
unsafeAccumUArray Float -> e' -> Float
f UArray i Float
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Float -> e' -> Float)
-> Float -> (i, i) -> [(Int, e')] -> UArray i Float
unsafeAccumArray Float -> e' -> Float
f Float
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Float)) -> UArray i Float
forall a. (forall s. ST s a) -> a
runST ((Float -> e' -> Float)
-> Float -> (i, i) -> [(Int, e')] -> ST s (UArray i Float)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Float (ST s)
unsafeAccumArrayUArray Float -> e' -> Float
f Float
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Double where
    {-# INLINE bounds #-}
    bounds :: UArray i Double -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Double -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Double)] -> UArray i Double
unsafeArray (i, i)
lu [(Int, Double)]
ies = (forall s. ST s (UArray i Double)) -> UArray i Double
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Double)] -> Double -> ST s (UArray i Double)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Double (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Double)]
ies Double
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Double -> Int -> Double
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Double# -> Double
D# (ByteArray# -> Int# -> Double#
indexDoubleArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Double -> [(Int, Double)] -> UArray i Double
unsafeReplace UArray i Double
arr [(Int, Double)]
ies = (forall s. ST s (UArray i Double)) -> UArray i Double
forall a. (forall s. ST s a) -> a
runST (UArray i Double -> [(Int, Double)] -> ST s (UArray i Double)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Double (ST s)
unsafeReplaceUArray UArray i Double
arr [(Int, Double)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Double -> e' -> Double)
-> UArray i Double -> [(Int, e')] -> UArray i Double
unsafeAccum Double -> e' -> Double
f UArray i Double
arr [(Int, e')]
ies = (forall s. ST s (UArray i Double)) -> UArray i Double
forall a. (forall s. ST s a) -> a
runST ((Double -> e' -> Double)
-> UArray i Double -> [(Int, e')] -> ST s (UArray i Double)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Double (ST s)
unsafeAccumUArray Double -> e' -> Double
f UArray i Double
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Double -> e' -> Double)
-> Double -> (i, i) -> [(Int, e')] -> UArray i Double
unsafeAccumArray Double -> e' -> Double
f Double
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Double)) -> UArray i Double
forall a. (forall s. ST s a) -> a
runST ((Double -> e' -> Double)
-> Double -> (i, i) -> [(Int, e')] -> ST s (UArray i Double)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Double (ST s)
unsafeAccumArrayUArray Double -> e' -> Double
f Double
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray (StablePtr a) where
    {-# INLINE bounds #-}
    bounds :: UArray i (StablePtr a) -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i (StablePtr a) -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, StablePtr a)] -> UArray i (StablePtr a)
unsafeArray (i, i)
lu [(Int, StablePtr a)]
ies = (forall s. ST s (UArray i (StablePtr a))) -> UArray i (StablePtr a)
forall a. (forall s. ST s a) -> a
runST ((i, i)
-> [(Int, StablePtr a)]
-> StablePtr a
-> ST s (UArray i (StablePtr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (StablePtr a) (ST s)
unsafeArrayUArray (i, i)
lu [(Int, StablePtr a)]
ies StablePtr a
forall a. StablePtr a
nullStablePtr)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i (StablePtr a) -> Int -> StablePtr a
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = StablePtr# a -> StablePtr a
forall a. StablePtr# a -> StablePtr a
StablePtr (ByteArray# -> Int# -> StablePtr# a
forall a. ByteArray# -> Int# -> StablePtr# a
indexStablePtrArray# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i (StablePtr a)
-> [(Int, StablePtr a)] -> UArray i (StablePtr a)
unsafeReplace UArray i (StablePtr a)
arr [(Int, StablePtr a)]
ies = (forall s. ST s (UArray i (StablePtr a))) -> UArray i (StablePtr a)
forall a. (forall s. ST s a) -> a
runST (UArray i (StablePtr a)
-> [(Int, StablePtr a)] -> ST s (UArray i (StablePtr a))
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (StablePtr a) (ST s)
unsafeReplaceUArray UArray i (StablePtr a)
arr [(Int, StablePtr a)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (StablePtr a -> e' -> StablePtr a)
-> UArray i (StablePtr a) -> [(Int, e')] -> UArray i (StablePtr a)
unsafeAccum StablePtr a -> e' -> StablePtr a
f UArray i (StablePtr a)
arr [(Int, e')]
ies = (forall s. ST s (UArray i (StablePtr a))) -> UArray i (StablePtr a)
forall a. (forall s. ST s a) -> a
runST ((StablePtr a -> e' -> StablePtr a)
-> UArray i (StablePtr a)
-> [(Int, e')]
-> ST s (UArray i (StablePtr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (StablePtr a) (ST s)
unsafeAccumUArray StablePtr a -> e' -> StablePtr a
f UArray i (StablePtr a)
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (StablePtr a -> e' -> StablePtr a)
-> StablePtr a -> (i, i) -> [(Int, e')] -> UArray i (StablePtr a)
unsafeAccumArray StablePtr a -> e' -> StablePtr a
f StablePtr a
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i (StablePtr a))) -> UArray i (StablePtr a)
forall a. (forall s. ST s a) -> a
runST ((StablePtr a -> e' -> StablePtr a)
-> StablePtr a
-> (i, i)
-> [(Int, e')]
-> ST s (UArray i (StablePtr a))
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (StablePtr a) (ST s)
unsafeAccumArrayUArray StablePtr a -> e' -> StablePtr a
f StablePtr a
initialValue (i, i)
lu [(Int, e')]
ies)

-- bogus StablePtr value for initialising a UArray of StablePtr.
nullStablePtr :: StablePtr a
nullStablePtr :: StablePtr a
nullStablePtr = StablePtr# a -> StablePtr a
forall a. StablePtr# a -> StablePtr a
StablePtr (Int# -> StablePtr# a
unsafeCoerce# Int#
0#)

instance IArray UArray Int8 where
    {-# INLINE bounds #-}
    bounds :: UArray i Int8 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Int8 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Int8)] -> UArray i Int8
unsafeArray (i, i)
lu [(Int, Int8)]
ies = (forall s. ST s (UArray i Int8)) -> UArray i Int8
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Int8)] -> Int8 -> ST s (UArray i Int8)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int8 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Int8)]
ies Int8
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Int8 -> Int -> Int8
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Int8
I8# (ByteArray# -> Int# -> Int#
indexInt8Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Int8 -> [(Int, Int8)] -> UArray i Int8
unsafeReplace UArray i Int8
arr [(Int, Int8)]
ies = (forall s. ST s (UArray i Int8)) -> UArray i Int8
forall a. (forall s. ST s a) -> a
runST (UArray i Int8 -> [(Int, Int8)] -> ST s (UArray i Int8)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int8 (ST s)
unsafeReplaceUArray UArray i Int8
arr [(Int, Int8)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Int8 -> e' -> Int8)
-> UArray i Int8 -> [(Int, e')] -> UArray i Int8
unsafeAccum Int8 -> e' -> Int8
f UArray i Int8
arr [(Int, e')]
ies = (forall s. ST s (UArray i Int8)) -> UArray i Int8
forall a. (forall s. ST s a) -> a
runST ((Int8 -> e' -> Int8)
-> UArray i Int8 -> [(Int, e')] -> ST s (UArray i Int8)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int8 (ST s)
unsafeAccumUArray Int8 -> e' -> Int8
f UArray i Int8
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Int8 -> e' -> Int8)
-> Int8 -> (i, i) -> [(Int, e')] -> UArray i Int8
unsafeAccumArray Int8 -> e' -> Int8
f Int8
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Int8)) -> UArray i Int8
forall a. (forall s. ST s a) -> a
runST ((Int8 -> e' -> Int8)
-> Int8 -> (i, i) -> [(Int, e')] -> ST s (UArray i Int8)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int8 (ST s)
unsafeAccumArrayUArray Int8 -> e' -> Int8
f Int8
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Int16 where
    {-# INLINE bounds #-}
    bounds :: UArray i Int16 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Int16 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Int16)] -> UArray i Int16
unsafeArray (i, i)
lu [(Int, Int16)]
ies = (forall s. ST s (UArray i Int16)) -> UArray i Int16
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Int16)] -> Int16 -> ST s (UArray i Int16)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int16 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Int16)]
ies Int16
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Int16 -> Int -> Int16
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Int16
I16# (ByteArray# -> Int# -> Int#
indexInt16Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Int16 -> [(Int, Int16)] -> UArray i Int16
unsafeReplace UArray i Int16
arr [(Int, Int16)]
ies = (forall s. ST s (UArray i Int16)) -> UArray i Int16
forall a. (forall s. ST s a) -> a
runST (UArray i Int16 -> [(Int, Int16)] -> ST s (UArray i Int16)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int16 (ST s)
unsafeReplaceUArray UArray i Int16
arr [(Int, Int16)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Int16 -> e' -> Int16)
-> UArray i Int16 -> [(Int, e')] -> UArray i Int16
unsafeAccum Int16 -> e' -> Int16
f UArray i Int16
arr [(Int, e')]
ies = (forall s. ST s (UArray i Int16)) -> UArray i Int16
forall a. (forall s. ST s a) -> a
runST ((Int16 -> e' -> Int16)
-> UArray i Int16 -> [(Int, e')] -> ST s (UArray i Int16)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int16 (ST s)
unsafeAccumUArray Int16 -> e' -> Int16
f UArray i Int16
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Int16 -> e' -> Int16)
-> Int16 -> (i, i) -> [(Int, e')] -> UArray i Int16
unsafeAccumArray Int16 -> e' -> Int16
f Int16
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Int16)) -> UArray i Int16
forall a. (forall s. ST s a) -> a
runST ((Int16 -> e' -> Int16)
-> Int16 -> (i, i) -> [(Int, e')] -> ST s (UArray i Int16)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int16 (ST s)
unsafeAccumArrayUArray Int16 -> e' -> Int16
f Int16
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Int32 where
    {-# INLINE bounds #-}
    bounds :: UArray i Int32 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Int32 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Int32)] -> UArray i Int32
unsafeArray (i, i)
lu [(Int, Int32)]
ies = (forall s. ST s (UArray i Int32)) -> UArray i Int32
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Int32)] -> Int32 -> ST s (UArray i Int32)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int32 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Int32)]
ies Int32
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Int32 -> Int -> Int32
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Int32
I32# (ByteArray# -> Int# -> Int#
indexInt32Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Int32 -> [(Int, Int32)] -> UArray i Int32
unsafeReplace UArray i Int32
arr [(Int, Int32)]
ies = (forall s. ST s (UArray i Int32)) -> UArray i Int32
forall a. (forall s. ST s a) -> a
runST (UArray i Int32 -> [(Int, Int32)] -> ST s (UArray i Int32)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int32 (ST s)
unsafeReplaceUArray UArray i Int32
arr [(Int, Int32)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Int32 -> e' -> Int32)
-> UArray i Int32 -> [(Int, e')] -> UArray i Int32
unsafeAccum Int32 -> e' -> Int32
f UArray i Int32
arr [(Int, e')]
ies = (forall s. ST s (UArray i Int32)) -> UArray i Int32
forall a. (forall s. ST s a) -> a
runST ((Int32 -> e' -> Int32)
-> UArray i Int32 -> [(Int, e')] -> ST s (UArray i Int32)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int32 (ST s)
unsafeAccumUArray Int32 -> e' -> Int32
f UArray i Int32
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Int32 -> e' -> Int32)
-> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32
unsafeAccumArray Int32 -> e' -> Int32
f Int32
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Int32)) -> UArray i Int32
forall a. (forall s. ST s a) -> a
runST ((Int32 -> e' -> Int32)
-> Int32 -> (i, i) -> [(Int, e')] -> ST s (UArray i Int32)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int32 (ST s)
unsafeAccumArrayUArray Int32 -> e' -> Int32
f Int32
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Int64 where
    {-# INLINE bounds #-}
    bounds :: UArray i Int64 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Int64 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Int64)] -> UArray i Int64
unsafeArray (i, i)
lu [(Int, Int64)]
ies = (forall s. ST s (UArray i Int64)) -> UArray i Int64
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Int64)] -> Int64 -> ST s (UArray i Int64)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int64 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Int64)]
ies Int64
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Int64 -> Int -> Int64
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Int# -> Int64
I64# (ByteArray# -> Int# -> Int#
indexInt64Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Int64 -> [(Int, Int64)] -> UArray i Int64
unsafeReplace UArray i Int64
arr [(Int, Int64)]
ies = (forall s. ST s (UArray i Int64)) -> UArray i Int64
forall a. (forall s. ST s a) -> a
runST (UArray i Int64 -> [(Int, Int64)] -> ST s (UArray i Int64)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int64 (ST s)
unsafeReplaceUArray UArray i Int64
arr [(Int, Int64)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Int64 -> e' -> Int64)
-> UArray i Int64 -> [(Int, e')] -> UArray i Int64
unsafeAccum Int64 -> e' -> Int64
f UArray i Int64
arr [(Int, e')]
ies = (forall s. ST s (UArray i Int64)) -> UArray i Int64
forall a. (forall s. ST s a) -> a
runST ((Int64 -> e' -> Int64)
-> UArray i Int64 -> [(Int, e')] -> ST s (UArray i Int64)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int64 (ST s)
unsafeAccumUArray Int64 -> e' -> Int64
f UArray i Int64
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Int64 -> e' -> Int64)
-> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64
unsafeAccumArray Int64 -> e' -> Int64
f Int64
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Int64)) -> UArray i Int64
forall a. (forall s. ST s a) -> a
runST ((Int64 -> e' -> Int64)
-> Int64 -> (i, i) -> [(Int, e')] -> ST s (UArray i Int64)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int64 (ST s)
unsafeAccumArrayUArray Int64 -> e' -> Int64
f Int64
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Word8 where
    {-# INLINE bounds #-}
    bounds :: UArray i Word8 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Word8 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Word8)] -> UArray i Word8
unsafeArray (i, i)
lu [(Int, Word8)]
ies = (forall s. ST s (UArray i Word8)) -> UArray i Word8
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Word8)] -> Word8 -> ST s (UArray i Word8)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word8 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Word8)]
ies Word8
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Word8 -> Int -> Word8
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Word# -> Word8
W8# (ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Word8 -> [(Int, Word8)] -> UArray i Word8
unsafeReplace UArray i Word8
arr [(Int, Word8)]
ies = (forall s. ST s (UArray i Word8)) -> UArray i Word8
forall a. (forall s. ST s a) -> a
runST (UArray i Word8 -> [(Int, Word8)] -> ST s (UArray i Word8)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word8 (ST s)
unsafeReplaceUArray UArray i Word8
arr [(Int, Word8)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Word8 -> e' -> Word8)
-> UArray i Word8 -> [(Int, e')] -> UArray i Word8
unsafeAccum Word8 -> e' -> Word8
f UArray i Word8
arr [(Int, e')]
ies = (forall s. ST s (UArray i Word8)) -> UArray i Word8
forall a. (forall s. ST s a) -> a
runST ((Word8 -> e' -> Word8)
-> UArray i Word8 -> [(Int, e')] -> ST s (UArray i Word8)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word8 (ST s)
unsafeAccumUArray Word8 -> e' -> Word8
f UArray i Word8
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Word8 -> e' -> Word8)
-> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8
unsafeAccumArray Word8 -> e' -> Word8
f Word8
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Word8)) -> UArray i Word8
forall a. (forall s. ST s a) -> a
runST ((Word8 -> e' -> Word8)
-> Word8 -> (i, i) -> [(Int, e')] -> ST s (UArray i Word8)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word8 (ST s)
unsafeAccumArrayUArray Word8 -> e' -> Word8
f Word8
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Word16 where
    {-# INLINE bounds #-}
    bounds :: UArray i Word16 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Word16 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Word16)] -> UArray i Word16
unsafeArray (i, i)
lu [(Int, Word16)]
ies = (forall s. ST s (UArray i Word16)) -> UArray i Word16
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Word16)] -> Word16 -> ST s (UArray i Word16)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word16 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Word16)]
ies Word16
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Word16 -> Int -> Word16
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Word# -> Word16
W16# (ByteArray# -> Int# -> Word#
indexWord16Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Word16 -> [(Int, Word16)] -> UArray i Word16
unsafeReplace UArray i Word16
arr [(Int, Word16)]
ies = (forall s. ST s (UArray i Word16)) -> UArray i Word16
forall a. (forall s. ST s a) -> a
runST (UArray i Word16 -> [(Int, Word16)] -> ST s (UArray i Word16)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word16 (ST s)
unsafeReplaceUArray UArray i Word16
arr [(Int, Word16)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Word16 -> e' -> Word16)
-> UArray i Word16 -> [(Int, e')] -> UArray i Word16
unsafeAccum Word16 -> e' -> Word16
f UArray i Word16
arr [(Int, e')]
ies = (forall s. ST s (UArray i Word16)) -> UArray i Word16
forall a. (forall s. ST s a) -> a
runST ((Word16 -> e' -> Word16)
-> UArray i Word16 -> [(Int, e')] -> ST s (UArray i Word16)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word16 (ST s)
unsafeAccumUArray Word16 -> e' -> Word16
f UArray i Word16
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Word16 -> e' -> Word16)
-> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16
unsafeAccumArray Word16 -> e' -> Word16
f Word16
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Word16)) -> UArray i Word16
forall a. (forall s. ST s a) -> a
runST ((Word16 -> e' -> Word16)
-> Word16 -> (i, i) -> [(Int, e')] -> ST s (UArray i Word16)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word16 (ST s)
unsafeAccumArrayUArray Word16 -> e' -> Word16
f Word16
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Word32 where
    {-# INLINE bounds #-}
    bounds :: UArray i Word32 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Word32 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Word32)] -> UArray i Word32
unsafeArray (i, i)
lu [(Int, Word32)]
ies = (forall s. ST s (UArray i Word32)) -> UArray i Word32
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Word32)] -> Word32 -> ST s (UArray i Word32)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word32 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Word32)]
ies Word32
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Word32 -> Int -> Word32
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Word# -> Word32
W32# (ByteArray# -> Int# -> Word#
indexWord32Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Word32 -> [(Int, Word32)] -> UArray i Word32
unsafeReplace UArray i Word32
arr [(Int, Word32)]
ies = (forall s. ST s (UArray i Word32)) -> UArray i Word32
forall a. (forall s. ST s a) -> a
runST (UArray i Word32 -> [(Int, Word32)] -> ST s (UArray i Word32)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word32 (ST s)
unsafeReplaceUArray UArray i Word32
arr [(Int, Word32)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Word32 -> e' -> Word32)
-> UArray i Word32 -> [(Int, e')] -> UArray i Word32
unsafeAccum Word32 -> e' -> Word32
f UArray i Word32
arr [(Int, e')]
ies = (forall s. ST s (UArray i Word32)) -> UArray i Word32
forall a. (forall s. ST s a) -> a
runST ((Word32 -> e' -> Word32)
-> UArray i Word32 -> [(Int, e')] -> ST s (UArray i Word32)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word32 (ST s)
unsafeAccumUArray Word32 -> e' -> Word32
f UArray i Word32
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Word32 -> e' -> Word32)
-> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32
unsafeAccumArray Word32 -> e' -> Word32
f Word32
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Word32)) -> UArray i Word32
forall a. (forall s. ST s a) -> a
runST ((Word32 -> e' -> Word32)
-> Word32 -> (i, i) -> [(Int, e')] -> ST s (UArray i Word32)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word32 (ST s)
unsafeAccumArrayUArray Word32 -> e' -> Word32
f Word32
initialValue (i, i)
lu [(Int, e')]
ies)

instance IArray UArray Word64 where
    {-# INLINE bounds #-}
    bounds :: UArray i Word64 -> (i, i)
bounds (UArray i
l i
u Int
_ ByteArray#
_) = (i
l,i
u)
    {-# INLINE numElements #-}
    numElements :: UArray i Word64 -> Int
numElements (UArray i
_ i
_ Int
n ByteArray#
_) = Int
n
    {-# INLINE unsafeArray #-}
    unsafeArray :: (i, i) -> [(Int, Word64)] -> UArray i Word64
unsafeArray (i, i)
lu [(Int, Word64)]
ies = (forall s. ST s (UArray i Word64)) -> UArray i Word64
forall a. (forall s. ST s a) -> a
runST ((i, i) -> [(Int, Word64)] -> Word64 -> ST s (UArray i Word64)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
(i, i) -> [(Int, e)] -> e -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word64 (ST s)
unsafeArrayUArray (i, i)
lu [(Int, Word64)]
ies Word64
0)
    {-# INLINE unsafeAt #-}
    unsafeAt :: UArray i Word64 -> Int -> Word64
unsafeAt (UArray i
_ i
_ Int
_ ByteArray#
arr#) (I# Int#
i#) = Word# -> Word64
W64# (ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr# Int#
i#)
    {-# INLINE unsafeReplace #-}
    unsafeReplace :: UArray i Word64 -> [(Int, Word64)] -> UArray i Word64
unsafeReplace UArray i Word64
arr [(Int, Word64)]
ies = (forall s. ST s (UArray i Word64)) -> UArray i Word64
forall a. (forall s. ST s a) -> a
runST (UArray i Word64 -> [(Int, Word64)] -> ST s (UArray i Word64)
forall s e i.
(MArray (STUArray s) e (ST s), Ix i) =>
UArray i e -> [(Int, e)] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word64 (ST s)
unsafeReplaceUArray UArray i Word64
arr [(Int, Word64)]
ies)
    {-# INLINE unsafeAccum #-}
    unsafeAccum :: (Word64 -> e' -> Word64)
-> UArray i Word64 -> [(Int, e')] -> UArray i Word64
unsafeAccum Word64 -> e' -> Word64
f UArray i Word64
arr [(Int, e')]
ies = (forall s. ST s (UArray i Word64)) -> UArray i Word64
forall a. (forall s. ST s a) -> a
runST ((Word64 -> e' -> Word64)
-> UArray i Word64 -> [(Int, e')] -> ST s (UArray i Word64)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> UArray i e -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word64 (ST s)
unsafeAccumUArray Word64 -> e' -> Word64
f UArray i Word64
arr [(Int, e')]
ies)
    {-# INLINE unsafeAccumArray #-}
    unsafeAccumArray :: (Word64 -> e' -> Word64)
-> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64
unsafeAccumArray Word64 -> e' -> Word64
f Word64
initialValue (i, i)
lu [(Int, e')]
ies = (forall s. ST s (UArray i Word64)) -> UArray i Word64
forall a. (forall s. ST s a) -> a
runST ((Word64 -> e' -> Word64)
-> Word64 -> (i, i) -> [(Int, e')] -> ST s (UArray i Word64)
forall s e i e'.
(MArray (STUArray s) e (ST s), Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> ST s (UArray i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word64 (ST s)
unsafeAccumArrayUArray Word64 -> e' -> Word64
f Word64
initialValue (i, i)
lu [(Int, e')]
ies)

instance (Ix ix, Eq e, IArray UArray e) => Eq (UArray ix e) where
    == :: UArray ix e -> UArray ix e -> Bool
(==) = UArray ix e -> UArray ix e -> Bool
forall e i.
(IArray UArray e, Ix i, Eq e) =>
UArray i e -> UArray i e -> Bool
Evidence bound by a type signature of the constraint type Eq e
Evidence bound by a type signature of the constraint type Ix ix
Evidence bound by a type signature of the constraint type IArray UArray e
eqUArray

instance (Ix ix, Ord e, IArray UArray e) => Ord (UArray ix e) where
    compare :: UArray ix e -> UArray ix e -> Ordering
compare = UArray ix e -> UArray ix e -> Ordering
forall e i.
(IArray UArray e, Ix i, Ord e) =>
UArray i e -> UArray i e -> Ordering
Evidence bound by a type signature of the constraint type Ord e
Evidence bound by a type signature of the constraint type Ix ix
Evidence bound by a type signature of the constraint type IArray UArray e
cmpUArray

instance (Ix ix, Show ix, Show e, IArray UArray e) => Show (UArray ix e) where
    showsPrec :: Int -> UArray ix e -> [Char] -> [Char]
showsPrec = Int -> UArray ix e -> [Char] -> [Char]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i, Show i, Show e) =>
Int -> a i e -> [Char] -> [Char]
Evidence bound by a type signature of the constraint type Show e
Evidence bound by a type signature of the constraint type Show ix
Evidence bound by a type signature of the constraint type Ix ix
Evidence bound by a type signature of the constraint type IArray UArray e
showsIArray

instance (Ix ix, Read ix, Read e, IArray UArray e) => Read (UArray ix e) where
    readPrec :: ReadPrec (UArray ix e)
readPrec = ReadPrec (UArray ix e)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i, Read i, Read e) =>
ReadPrec (a i e)
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read ix
Evidence bound by a type signature of the constraint type Ix ix
Evidence bound by a type signature of the constraint type IArray UArray e
readIArray

-----------------------------------------------------------------------------
-- Mutable arrays

{-# NOINLINE arrEleBottom #-}
arrEleBottom :: a
arrEleBottom :: a
arrEleBottom = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"MArray: undefined array element"

{-| Class of mutable array types.

An array type has the form @(a i e)@ where @a@ is the array type
constructor (kind @* -> * -> *@), @i@ is the index type (a member of
the class 'Ix'), and @e@ is the element type.

The @MArray@ class is parameterised over both @a@ and @e@ (so that
instances specialised to certain element types can be defined, in the
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
    getBounds      :: Ix i => a i e -> m (i,i)
    -- | 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
    -- value.
    newArray    :: Ix i => (i,i) -> e -> m (a i e)

    -- | Builds a new array, with every element initialised to an
    -- undefined value. In a monadic context in which operations must
    -- be deterministic (e.g. the ST monad), the array elements are
    -- initialised to a fixed but undefined value, such as zero.
    newArray_ :: Ix i => (i,i) -> m (a i e)

    -- | Builds a new array, with every element initialised to an undefined
    -- value.
    unsafeNewArray_ :: Ix i => (i,i) -> m (a i e)

    unsafeRead  :: Ix i => a i e -> Int -> m e
    unsafeWrite :: Ix i => a i e -> Int -> e -> m ()

    {-# INLINE newArray #-}
        -- The INLINE is crucial, because until we know at least which monad
        -- we are in, the code below allocates like crazy.  So inline it,
        -- in the hope that the context will know the monad.
    newArray (i
l,i
u) e
initialValue = do
        let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
        a i e
marr <- (i, i) -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeNewArray_ (i
l,i
u)
        [m ()] -> m ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
External instance of the constraint type Foldable []
sequence_ [a i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeWrite a i e
marr Int
i e
initialValue | Int
i <- [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]
        a i e -> m (a i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return a i e
marr

    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ (i
l,i
u) = (i, i) -> e -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
newArray (i
l,i
u) e
forall a. a
arrEleBottom

    {-# INLINE newArray_ #-}
    newArray_ (i
l,i
u) = (i, i) -> e -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
newArray (i
l,i
u) e
forall a. a
arrEleBottom

    -- newArray takes an initialiser which all elements of
    -- the newly created array are initialised to.  unsafeNewArray_ takes
    -- no initialiser, it is assumed that the array is initialised with
    -- "undefined" values.

    -- why not omit unsafeNewArray_?  Because in the unboxed array
    -- case we would like to omit the initialisation altogether if
    -- possible.  We can't do this for boxed arrays, because the
    -- elements must all have valid values at all times in case of
    -- garbage collection.

    -- why not omit newArray?  Because in the boxed case, we can omit the
    -- default initialisation with undefined values if we *do* know the
    -- initial value and it is constant for all elements.

instance MArray IOArray e IO where
    {-# INLINE getBounds #-}
    getBounds :: IOArray i e -> IO (i, i)
getBounds (IOArray STArray RealWorld i e
marr) = ST RealWorld (i, i) -> IO (i, i)
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld (i, i) -> IO (i, i))
-> ST RealWorld (i, i) -> IO (i, i)
forall a b. (a -> b) -> a -> b
$ STArray RealWorld i e -> ST RealWorld (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
getBounds STArray RealWorld i e
marr
    {-# INLINE getNumElements #-}
    getNumElements :: IOArray i e -> IO Int
getNumElements (IOArray STArray RealWorld i e
marr) = ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld Int -> IO Int) -> ST RealWorld Int -> IO Int
forall a b. (a -> b) -> a -> b
$ STArray RealWorld i e -> ST RealWorld Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s e. MArray (STArray s) e (ST s)
getNumElements STArray RealWorld i e
marr
    newArray :: (i, i) -> e -> IO (IOArray i e)
newArray    = (i, i) -> e -> IO (IOArray i e)
forall i e. Ix i => (i, i) -> e -> IO (IOArray i e)
Evidence bound by a type signature of the constraint type Ix i
newIOArray
    unsafeRead :: IOArray i e -> Int -> IO e
unsafeRead  = IOArray i e -> Int -> IO e
forall i e. IOArray i e -> Int -> IO e
unsafeReadIOArray
    unsafeWrite :: IOArray i e -> Int -> e -> IO ()
unsafeWrite = IOArray i e -> Int -> e -> IO ()
forall i e. IOArray i e -> Int -> e -> IO ()
unsafeWriteIOArray

{-# INLINE newListArray #-}
-- | Constructs a mutable array from a list of initial elements.
-- The list gives the elements of the array in ascending order
-- beginning with the lowest index.
newListArray :: (MArray a e m, Ix i) => (i,i) -> [e] -> m (a i e)
newListArray :: (i, i) -> [e] -> m (a i e)
newListArray (i
l,i
u) [e]
es = do
    a i e
marr <- (i, i) -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
newArray_ (i
l,i
u)
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
    let fillFromList :: Int -> [e] -> m ()
fillFromList Int
i [e]
xs | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
n    = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return ()
                          | Bool
otherwise = case [e]
xs of
            []   -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return ()
            e
y:[e]
ys -> a i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeWrite a i e
marr Int
i e
y m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
>> Int -> [e] -> m ()
fillFromList (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) [e]
ys
    Int -> [e] -> m ()
forall {m :: * -> *}. MArray a e m => Int -> [e] -> m ()
Evidence bound by a type signature of the constraint type MArray a e m
fillFromList Int
0 [e]
es
    a i e -> m (a i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return a i e
marr

{-# INLINE readArray #-}
-- | Read an element from a mutable array
readArray :: (MArray a e m, Ix i) => a i e -> i -> m e
readArray :: a i e -> i -> m e
readArray a i e
marr i
i = do
  (i
l,i
u) <- a i e -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getBounds a i e
marr
  Int
n <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr
  a i e -> Int -> m e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeRead a i e
marr ((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i)

{-# INLINE writeArray #-}
-- | Write an element in a mutable array
writeArray :: (MArray a e m, Ix i) => a i e -> i -> e -> m ()
writeArray :: a i e -> i -> e -> m ()
writeArray a i e
marr i
i e
e = do
  (i
l,i
u) <- a i e -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getBounds a i e
marr
  Int
n <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr
  a i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeWrite a i e
marr ((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i) e
e

{-# INLINE getElems #-}
-- | Return a list of all the elements of a mutable array
getElems :: (MArray a e m, Ix i) => a i e -> m [e]
getElems :: a i e -> m [e]
getElems a i e
marr = do
  (i
_l, i
_u) <- a i e -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getBounds a i e
marr
  Int
n <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr
  [m e] -> m [e]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
External instance of the constraint type Traversable []
sequence [a i e -> Int -> m e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeRead a i e
marr Int
i | Int
i <- [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]

{-# INLINE getAssocs #-}
-- | Return a list of all the associations of a mutable array, in
-- index order.
getAssocs :: (MArray a e m, Ix i) => a i e -> m [(i, e)]
getAssocs :: a i e -> m [(i, e)]
getAssocs a i e
marr = do
  (i
l,i
u) <- a i e -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getBounds a i e
marr
  Int
n <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr
  [m (i, e)] -> m [(i, e)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
External instance of the constraint type Traversable []
sequence [ do e
e <- a i e -> Int -> m e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeRead a i e
marr ((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l,i
u) Int
n i
i); (i, e) -> m (i, e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return (i
i,e
e)
           | i
i <- (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
Evidence bound by a type signature of the constraint type Ix i
range (i
l,i
u)]

{-# INLINE mapArray #-}
-- | Constructs a new array derived from the original array by applying a
-- function to each of the elements.
mapArray :: (MArray a e' m, MArray a e m, Ix i) => (e' -> e) -> a i e' -> m (a i e)
mapArray :: (e' -> e) -> a i e' -> m (a i e)
mapArray e' -> e
f a i e'
marr = do
  (i
l,i
u) <- a i e' -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e' m
getBounds a i e'
marr
  Int
n <- a i e' -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e' m
getNumElements a i e'
marr
  a i e
marr' <- (i, i) -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
newArray_ (i
l,i
u)
  [m ()] -> m ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e' m
External instance of the constraint type Foldable []
sequence_ [do e'
e <- a i e' -> Int -> m e'
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e' m
unsafeRead a i e'
marr Int
i
                a i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeWrite a i e
marr' Int
i (e' -> e
f e'
e)
            | Int
i <- [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]
  a i e -> m (a i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e' m
return a i e
marr'

{-# INLINE mapIndices #-}
-- | Constructs a new array derived from the original array by applying a
-- function to each of the indices.
mapIndices :: (MArray a e m, Ix i, Ix j) => (i,i) -> (i -> j) -> a j e -> m (a i e)
mapIndices :: (i, i) -> (i -> j) -> a j e -> m (a i e)
mapIndices (i
l',i
u') i -> j
f a j e
marr = do
    a i e
marr' <- (i, i) -> m (a i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
newArray_ (i
l',i
u')
    Int
n' <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr'
    [m ()] -> m ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
External instance of the constraint type Foldable []
sequence_ [do e
e <- a j e -> j -> m e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
Evidence bound by a type signature of the constraint type Ix j
Evidence bound by a type signature of the constraint type MArray a e m
readArray a j e
marr (i -> j
f i
i')
                  a i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeWrite a i e
marr' ((i, i) -> Int -> i -> Int
forall i. Ix i => (i, i) -> Int -> i -> Int
Evidence bound by a type signature of the constraint type Ix i
safeIndex (i
l',i
u') Int
n' i
i') e
e
              | i
i' <- (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
Evidence bound by a type signature of the constraint type Ix i
range (i
l',i
u')]
    a i e -> m (a i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return a i e
marr'

-----------------------------------------------------------------------------
-- Polymorphic non-strict mutable arrays (ST monad)

instance MArray (STArray s) e (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STArray s i e -> ST s (i, i)
getBounds STArray s i e
arr = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return ((i, i) -> ST s (i, i)) -> (i, i) -> ST s (i, i)
forall a b. (a -> b) -> a -> b
$! STArray s i e -> (i, i)
forall s i e. STArray s i e -> (i, i)
ArrST.boundsSTArray STArray s i e
arr
    {-# INLINE getNumElements #-}
    getNumElements :: STArray s i e -> ST s Int
getNumElements STArray s i e
arr = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (Int -> ST s Int) -> Int -> ST s Int
forall a b. (a -> b) -> a -> b
$! STArray s i e -> Int
forall s i e. STArray s i e -> Int
ArrST.numElementsSTArray STArray s i e
arr
    {-# INLINE newArray #-}
    newArray :: (i, i) -> e -> ST s (STArray s i e)
newArray    = (i, i) -> e -> ST s (STArray s i e)
forall i e s. Ix i => (i, i) -> e -> ST s (STArray s i e)
Evidence bound by a type signature of the constraint type Ix i
ArrST.newSTArray
    {-# INLINE unsafeRead #-}
    unsafeRead :: STArray s i e -> Int -> ST s e
unsafeRead  = STArray s i e -> Int -> ST s e
forall s i e. STArray s i e -> Int -> ST s e
ArrST.unsafeReadSTArray
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STArray s i e -> Int -> e -> ST s ()
unsafeWrite = STArray s i e -> Int -> e -> ST s ()
forall s i e. STArray s i e -> Int -> e -> ST s ()
ArrST.unsafeWriteSTArray

instance MArray (STArray s) e (Lazy.ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STArray s i e -> ST s (i, i)
getBounds STArray s i e
arr = ST s (i, i) -> ST s (i, i)
forall s a. ST s a -> ST s a
strictToLazyST ((i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return ((i, i) -> ST s (i, i)) -> (i, i) -> ST s (i, i)
forall a b. (a -> b) -> a -> b
$! STArray s i e -> (i, i)
forall s i e. STArray s i e -> (i, i)
ArrST.boundsSTArray STArray s i e
arr)
    {-# INLINE getNumElements #-}
    getNumElements :: STArray s i e -> ST s Int
getNumElements STArray s i e
arr = ST s Int -> ST s Int
forall s a. ST s a -> ST s a
strictToLazyST (Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (Int -> ST s Int) -> Int -> ST s Int
forall a b. (a -> b) -> a -> b
$! STArray s i e -> Int
forall s i e. STArray s i e -> Int
ArrST.numElementsSTArray STArray s i e
arr)
    {-# INLINE newArray #-}
    newArray :: (i, i) -> e -> ST s (STArray s i e)
newArray (i
l,i
u) e
e    = ST s (STArray s i e) -> ST s (STArray s i e)
forall s a. ST s a -> ST s a
strictToLazyST ((i, i) -> e -> ST s (STArray s i e)
forall i e s. Ix i => (i, i) -> e -> ST s (STArray s i e)
Evidence bound by a type signature of the constraint type Ix i
ArrST.newSTArray (i
l,i
u) e
e)
    {-# INLINE unsafeRead #-}
    unsafeRead :: STArray s i e -> Int -> ST s e
unsafeRead STArray s i e
arr Int
i    = ST s e -> ST s e
forall s a. ST s a -> ST s a
strictToLazyST (STArray s i e -> Int -> ST s e
forall s i e. STArray s i e -> Int -> ST s e
ArrST.unsafeReadSTArray STArray s i e
arr Int
i)
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STArray s i e -> Int -> e -> ST s ()
unsafeWrite STArray s i e
arr Int
i e
e = ST s () -> ST s ()
forall s a. ST s a -> ST s a
strictToLazyST (STArray s i e -> Int -> e -> ST s ()
forall s i e. STArray s i e -> Int -> e -> ST s ()
ArrST.unsafeWriteSTArray STArray s i e
arr Int
i e
e)

-----------------------------------------------------------------------------
-- Flat unboxed mutable arrays (ST monad)

-- | A mutable array with unboxed elements, that can be manipulated in
-- the 'ST' monad.  The type arguments are as follows:
--
--  * @s@: the state variable argument for the 'ST' type
--
--  * @i@: the index type of the array (should be an instance of @Ix@)
--
--  * @e@: the element type of the array.  Only certain element types
--    are supported.
--
-- An 'STUArray' will generally be more efficient (in terms of both time
-- and space) than the equivalent boxed version ('STArray') with the same
-- element type.  However, 'STUArray' is strict in its elements - so
-- don\'t use 'STUArray' if you require the non-strictness that
-- 'STArray' provides.
data STUArray s i e = STUArray !i !i !Int (MutableByteArray# s)
-- The "ST" parameter must be nominal for the safety of the ST trick.
-- The other parameters have class constraints. See also #9220.
type role STUArray nominal nominal nominal

instance Eq (STUArray s i e) where
    STUArray i
_ i
_ Int
_ MutableByteArray# s
arr1# == :: STUArray s i e -> STUArray s i e -> Bool
== STUArray i
_ i
_ Int
_ MutableByteArray# s
arr2# =
        Int# -> Bool
isTrue# (MutableByteArray# s -> MutableByteArray# s -> Int#
forall d. MutableByteArray# d -> MutableByteArray# d -> Int#
sameMutableByteArray# MutableByteArray# s
arr1# MutableByteArray# s
arr2#)

{-# INLINE unsafeNewArraySTUArray_ #-}
unsafeNewArraySTUArray_ :: Ix i
                        => (i,i) -> (Int# -> Int#) -> ST s (STUArray s i e)
unsafeNewArraySTUArray_ :: (i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
elemsToBytes
 = case (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
rangeSize (i
l,i
u) of
       n :: Int
n@(I# Int#
n#) ->
           STRep s (STUArray s i e) -> ST s (STUArray s i e)
forall s a. STRep s a -> ST s a
ST (STRep s (STUArray s i e) -> ST s (STUArray s i e))
-> STRep s (STUArray s i e) -> ST s (STUArray s i e)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
               case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# (Int# -> Int#
elemsToBytes Int#
n#) State# s
s1# of
                   (# State# s
s2#, MutableByteArray# s
marr# #) ->
                       (# State# s
s2#, i -> i -> Int -> MutableByteArray# s -> STUArray s i e
forall s i e.
i -> i -> Int -> MutableByteArray# s -> STUArray s i e
STUArray i
l i
u Int
n MutableByteArray# s
marr# #)

instance MArray (STUArray s) Bool (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Bool -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Bool -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE newArray #-}
    newArray :: (i, i) -> Bool -> ST s (STUArray s i Bool)
newArray (i
l,i
u) Bool
initialValue = STRep s (STUArray s i Bool) -> ST s (STUArray s i Bool)
forall s a. STRep s a -> ST s a
ST (STRep s (STUArray s i Bool) -> ST s (STUArray s i Bool))
-> STRep s (STUArray s i Bool) -> ST s (STUArray s i Bool)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)                   of { n :: Int
n@(I# Int#
n#) ->
        case Int# -> Int#
bOOL_SCALE Int#
n#                         of { Int#
nbytes# ->
        case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
nbytes# State# s
s1#             of { (# State# s
s2#, MutableByteArray# s
marr# #) ->
        case MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
setByteArray# MutableByteArray# s
marr# Int#
0# Int#
nbytes# Int#
e# State# s
s2# of { State# s
s3# ->
        (# State# s
s3#, i -> i -> Int -> MutableByteArray# s -> STUArray s i Bool
forall s i e.
i -> i -> Int -> MutableByteArray# s -> STUArray s i e
STUArray i
l i
u Int
n MutableByteArray# s
marr# #) }}}}
      where
        !(I# Int#
e#) = if Bool
initialValue then Int
0xff else Int
0x0
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Bool)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Bool)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
bOOL_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Bool)
newArray_ (i, i)
arrBounds = (i, i) -> Bool -> ST s (STUArray s i Bool)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Bool (ST s)
newArray (i, i)
arrBounds Bool
False
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Bool -> Int -> ST s Bool
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Bool -> ST s Bool
forall s a. STRep s a -> ST s a
ST (STRep s Bool -> ST s Bool) -> STRep s Bool -> ST s Bool
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWordArray# MutableByteArray# s
marr# (Int# -> Int#
bOOL_INDEX Int#
i#) State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Int# -> Bool
isTrue# ((Word#
e# Word# -> Word# -> Word#
`and#` Int# -> Word#
bOOL_BIT Int#
i#) Word# -> Word# -> Int#
`neWord#` Int# -> Word#
int2Word# Int#
0#) :: Bool #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Bool -> Int -> Bool -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) Bool
e = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case Int# -> Int#
bOOL_INDEX Int#
i#              of { Int#
j# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWordArray# MutableByteArray# s
marr# Int#
j# State# s
s1# of { (# State# s
s2#, Word#
old# #) ->
        case if Bool
e then Word#
old# Word# -> Word# -> Word#
`or#` Int# -> Word#
bOOL_BIT Int#
i#
             else Word#
old# Word# -> Word# -> Word#
`and#` Int# -> Word#
bOOL_NOT_BIT Int#
i# of { Word#
e# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWordArray# MutableByteArray# s
marr# Int#
j# Word#
e# State# s
s2# of { State# s
s3# ->
        (# State# s
s3#, () #) }}}}

instance MArray (STUArray s) Char (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Char -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Char -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Char)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Char)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
4#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Char)
newArray_ (i, i)
arrBounds = (i, i) -> Char -> ST s (STUArray s i Char)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Char (ST s)
newArray (i, i)
arrBounds (Int -> Char
chr Int
0)
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Char -> Int -> ST s Char
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Char -> ST s Char
forall s a. STRep s a -> ST s a
ST (STRep s Char -> ST s Char) -> STRep s Char -> ST s Char
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
readWideCharArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Char#
e# #) ->
        (# State# s
s2#, Char# -> Char
C# Char#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Char -> Int -> Char -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (C# Char#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
writeWideCharArray# MutableByteArray# s
marr# Int#
i# Char#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Int (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Int -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Int -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Int)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Int)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
wORD_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Int)
newArray_ (i, i)
arrBounds = (i, i) -> Int -> ST s (STUArray s i Int)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int (ST s)
newArray (i, i)
arrBounds Int
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Int -> Int -> ST s Int
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Int -> ST s Int
forall s a. STRep s a -> ST s a
ST (STRep s Int -> ST s Int) -> STRep s Int -> ST s Int
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readIntArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Int#
e# #) ->
        (# State# s
s2#, Int# -> Int
I# Int#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Int -> Int -> Int -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (I# Int#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeIntArray# MutableByteArray# s
marr# Int#
i# Int#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Word (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Word -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Word -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Word)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Word)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
wORD_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Word)
newArray_ (i, i)
arrBounds = (i, i) -> Word -> ST s (STUArray s i Word)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word (ST s)
newArray (i, i)
arrBounds Word
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Word -> Int -> ST s Word
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Word -> ST s Word
forall s a. STRep s a -> ST s a
ST (STRep s Word -> ST s Word) -> STRep s Word -> ST s Word
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWordArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Word# -> Word
W# Word#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Word -> Int -> Word -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (W# Word#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWordArray# MutableByteArray# s
marr# Int#
i# Word#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) (Ptr a) (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i (Ptr a) -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i (Ptr a) -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i (Ptr a))
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i (Ptr a))
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
wORD_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i (Ptr a))
newArray_ (i, i)
arrBounds = (i, i) -> Ptr a -> ST s (STUArray s i (Ptr a))
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (Ptr a) (ST s)
newArray (i, i)
arrBounds Ptr a
forall a. Ptr a
nullPtr
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i (Ptr a) -> Int -> ST s (Ptr a)
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s (Ptr a) -> ST s (Ptr a)
forall s a. STRep s a -> ST s a
ST (STRep s (Ptr a) -> ST s (Ptr a))
-> STRep s (Ptr a) -> ST s (Ptr a)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
readAddrArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Addr#
e# #) ->
        (# State# s
s2#, Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr Addr#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i (Ptr a) -> Int -> Ptr a -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (Ptr Addr#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
writeAddrArray# MutableByteArray# s
marr# Int#
i# Addr#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) (FunPtr a) (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i (FunPtr a) -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i (FunPtr a) -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i (FunPtr a))
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i (FunPtr a))
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
wORD_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i (FunPtr a))
newArray_ (i, i)
arrBounds = (i, i) -> FunPtr a -> ST s (STUArray s i (FunPtr a))
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (FunPtr a) (ST s)
newArray (i, i)
arrBounds FunPtr a
forall a. FunPtr a
nullFunPtr
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i (FunPtr a) -> Int -> ST s (FunPtr a)
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s (FunPtr a) -> ST s (FunPtr a)
forall s a. STRep s a -> ST s a
ST (STRep s (FunPtr a) -> ST s (FunPtr a))
-> STRep s (FunPtr a) -> ST s (FunPtr a)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
readAddrArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Addr#
e# #) ->
        (# State# s
s2#, Addr# -> FunPtr a
forall a. Addr# -> FunPtr a
FunPtr Addr#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i (FunPtr a) -> Int -> FunPtr a -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (FunPtr Addr#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
writeAddrArray# MutableByteArray# s
marr# Int#
i# Addr#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Float (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Float -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Float -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Float)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Float)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
fLOAT_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Float)
newArray_ (i, i)
arrBounds = (i, i) -> Float -> ST s (STUArray s i Float)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Float (ST s)
newArray (i, i)
arrBounds Float
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Float -> Int -> ST s Float
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Float -> ST s Float
forall s a. STRep s a -> ST s a
ST (STRep s Float -> ST s Float) -> STRep s Float -> ST s Float
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
readFloatArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Float#
e# #) ->
        (# State# s
s2#, Float# -> Float
F# Float#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Float -> Int -> Float -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (F# Float#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
writeFloatArray# MutableByteArray# s
marr# Int#
i# Float#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Double (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Double -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Double -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Double)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Double)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
dOUBLE_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Double)
newArray_ (i, i)
arrBounds = (i, i) -> Double -> ST s (STUArray s i Double)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Double (ST s)
newArray (i, i)
arrBounds Double
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Double -> Int -> ST s Double
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Double -> ST s Double
forall s a. STRep s a -> ST s a
ST (STRep s Double -> ST s Double) -> STRep s Double -> ST s Double
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readDoubleArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Double#
e# #) ->
        (# State# s
s2#, Double# -> Double
D# Double#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Double -> Int -> Double -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (D# Double#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeDoubleArray# MutableByteArray# s
marr# Int#
i# Double#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) (StablePtr a) (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i (StablePtr a) -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i (StablePtr a) -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i (StablePtr a))
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i (StablePtr a))
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) Int# -> Int#
wORD_SCALE
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i (StablePtr a))
newArray_ (i, i)
arrBounds = (i, i) -> StablePtr a -> ST s (STUArray s i (StablePtr a))
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s a. MArray (STUArray s) (StablePtr a) (ST s)
newArray (i, i)
arrBounds (Ptr () -> StablePtr a
forall a. Ptr () -> StablePtr a
castPtrToStablePtr Ptr ()
forall a. Ptr a
nullPtr)
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i (StablePtr a) -> Int -> ST s (StablePtr a)
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s (StablePtr a) -> ST s (StablePtr a)
forall s a. STRep s a -> ST s a
ST (STRep s (StablePtr a) -> ST s (StablePtr a))
-> STRep s (StablePtr a) -> ST s (StablePtr a)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
forall d a.
MutableByteArray# d
-> Int# -> State# d -> (# State# d, StablePtr# a #)
readStablePtrArray# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, StablePtr# a
e# #) ->
        (# State# s
s2# , StablePtr# a -> StablePtr a
forall a. StablePtr# a -> StablePtr a
StablePtr StablePtr# a
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i (StablePtr a) -> Int -> StablePtr a -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (StablePtr StablePtr# a
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
forall d a.
MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
writeStablePtrArray# MutableByteArray# s
marr# Int#
i# StablePtr# a
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Int8 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Int8 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Int8 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Int8)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Int8)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (\Int#
x -> Int#
x)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Int8)
newArray_ (i, i)
arrBounds = (i, i) -> Int8 -> ST s (STUArray s i Int8)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int8 (ST s)
newArray (i, i)
arrBounds Int8
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Int8 -> Int -> ST s Int8
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Int8 -> ST s Int8
forall s a. STRep s a -> ST s a
ST (STRep s Int8 -> ST s Int8) -> STRep s Int8 -> ST s Int8
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readInt8Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Int#
e# #) ->
        (# State# s
s2#, Int# -> Int8
I8# Int#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Int8 -> Int -> Int8 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (I8# Int#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeInt8Array# MutableByteArray# s
marr# Int#
i# Int#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Int16 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Int16 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Int16 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Int16)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Int16)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
2#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Int16)
newArray_ (i, i)
arrBounds = (i, i) -> Int16 -> ST s (STUArray s i Int16)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int16 (ST s)
newArray (i, i)
arrBounds Int16
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Int16 -> Int -> ST s Int16
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Int16 -> ST s Int16
forall s a. STRep s a -> ST s a
ST (STRep s Int16 -> ST s Int16) -> STRep s Int16 -> ST s Int16
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readInt16Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Int#
e# #) ->
        (# State# s
s2#, Int# -> Int16
I16# Int#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Int16 -> Int -> Int16 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (I16# Int#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeInt16Array# MutableByteArray# s
marr# Int#
i# Int#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Int32 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Int32 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Int32 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Int32)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Int32)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
4#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Int32)
newArray_ (i, i)
arrBounds = (i, i) -> Int32 -> ST s (STUArray s i Int32)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int32 (ST s)
newArray (i, i)
arrBounds Int32
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Int32 -> Int -> ST s Int32
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Int32 -> ST s Int32
forall s a. STRep s a -> ST s a
ST (STRep s Int32 -> ST s Int32) -> STRep s Int32 -> ST s Int32
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readInt32Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Int#
e# #) ->
        (# State# s
s2#, Int# -> Int32
I32# Int#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Int32 -> Int -> Int32 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (I32# Int#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeInt32Array# MutableByteArray# s
marr# Int#
i# Int#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Int64 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Int64 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Int64 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Int64)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Int64)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
8#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Int64)
newArray_ (i, i)
arrBounds = (i, i) -> Int64 -> ST s (STUArray s i Int64)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Int64 (ST s)
newArray (i, i)
arrBounds Int64
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Int64 -> Int -> ST s Int64
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Int64 -> ST s Int64
forall s a. STRep s a -> ST s a
ST (STRep s Int64 -> ST s Int64) -> STRep s Int64 -> ST s Int64
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readInt64Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Int#
e# #) ->
        (# State# s
s2#, Int# -> Int64
I64# Int#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Int64 -> Int -> Int64 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (I64# Int#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeInt64Array# MutableByteArray# s
marr# Int#
i# Int#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Word8 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Word8 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Word8 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Word8)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Word8)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (\Int#
x -> Int#
x)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Word8)
newArray_ (i, i)
arrBounds = (i, i) -> Word8 -> ST s (STUArray s i Word8)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word8 (ST s)
newArray (i, i)
arrBounds Word8
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Word8 -> Int -> ST s Word8
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Word8 -> ST s Word8
forall s a. STRep s a -> ST s a
ST (STRep s Word8 -> ST s Word8) -> STRep s Word8 -> ST s Word8
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord8Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Word# -> Word8
W8# Word#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Word8 -> Int -> Word8 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (W8# Word#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# s
marr# Int#
i# Word#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Word16 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Word16 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Word16 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Word16)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Word16)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
2#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Word16)
newArray_ (i, i)
arrBounds = (i, i) -> Word16 -> ST s (STUArray s i Word16)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word16 (ST s)
newArray (i, i)
arrBounds Word16
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Word16 -> Int -> ST s Word16
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Word16 -> ST s Word16
forall s a. STRep s a -> ST s a
ST (STRep s Word16 -> ST s Word16) -> STRep s Word16 -> ST s Word16
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord16Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Word# -> Word16
W16# Word#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Word16 -> Int -> Word16 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (W16# Word#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord16Array# MutableByteArray# s
marr# Int#
i# Word#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Word32 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Word32 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Word32 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Word32)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Word32)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
4#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Word32)
newArray_ (i, i)
arrBounds = (i, i) -> Word32 -> ST s (STUArray s i Word32)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word32 (ST s)
newArray (i, i)
arrBounds Word32
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Word32 -> Int -> ST s Word32
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Word32 -> ST s Word32
forall s a. STRep s a -> ST s a
ST (STRep s Word32 -> ST s Word32) -> STRep s Word32 -> ST s Word32
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord32Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Word# -> Word32
W32# Word#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Word32 -> Int -> Word32 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (W32# Word#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord32Array# MutableByteArray# s
marr# Int#
i# Word#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

instance MArray (STUArray s) Word64 (ST s) where
    {-# INLINE getBounds #-}
    getBounds :: STUArray s i Word64 -> ST s (i, i)
getBounds (STUArray i
l i
u Int
_ MutableByteArray# s
_) = (i, i) -> ST s (i, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i
l,i
u)
    {-# INLINE getNumElements #-}
    getNumElements :: STUArray s i Word64 -> ST s Int
getNumElements (STUArray i
_ i
_ Int
n MutableByteArray# s
_) = Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return Int
n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ :: (i, i) -> ST s (STUArray s i Word64)
unsafeNewArray_ (i
l,i
u) = (i, i) -> (Int# -> Int#) -> ST s (STUArray s i Word64)
forall i s e.
Ix i =>
(i, i) -> (Int# -> Int#) -> ST s (STUArray s i e)
Evidence bound by a type signature of the constraint type Ix i
unsafeNewArraySTUArray_ (i
l,i
u) (Int# -> Int# -> Int#
safe_scale Int#
8#)
    {-# INLINE newArray_ #-}
    newArray_ :: (i, i) -> ST s (STUArray s i Word64)
newArray_ (i, i)
arrBounds = (i, i) -> Word64 -> ST s (STUArray s i Word64)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Instance of class: MArray of the constraint type forall s. MArray (STUArray s) Word64 (ST s)
newArray (i, i)
arrBounds Word64
0
    {-# INLINE unsafeRead #-}
    unsafeRead :: STUArray s i Word64 -> Int -> ST s Word64
unsafeRead (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) = STRep s Word64 -> ST s Word64
forall s a. STRep s a -> ST s a
ST (STRep s Word64 -> ST s Word64) -> STRep s Word64 -> ST s Word64
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord64Array# MutableByteArray# s
marr# Int#
i# State# s
s1# of { (# State# s
s2#, Word#
e# #) ->
        (# State# s
s2#, Word# -> Word64
W64# Word#
e# #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite :: STUArray s i Word64 -> Int -> Word64 -> ST s ()
unsafeWrite (STUArray i
_ i
_ Int
_ MutableByteArray# s
marr#) (I# Int#
i#) (W64# Word#
e#) = STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
        case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord64Array# MutableByteArray# s
marr# Int#
i# Word#
e# State# s
s1# of { State# s
s2# ->
        (# State# s
s2#, () #) }

-----------------------------------------------------------------------------
-- Translation between elements and bytes

bOOL_SCALE, wORD_SCALE, dOUBLE_SCALE, fLOAT_SCALE :: Int# -> Int#
bOOL_SCALE :: Int# -> Int#
bOOL_SCALE Int#
n# =
    -- + 7 to handle case where n is not divisible by 8
    (Int#
n# Int# -> Int# -> Int#
+# Int#
7#) Int# -> Int# -> Int#
`uncheckedIShiftRA#` Int#
3#
wORD_SCALE :: Int# -> Int#
wORD_SCALE   Int#
n# = Int# -> Int# -> Int#
safe_scale Int#
scale# Int#
n# where !(I# Int#
scale#) = SIZEOF_HSWORD
dOUBLE_SCALE :: Int# -> Int#
dOUBLE_SCALE Int#
n# = Int# -> Int# -> Int#
safe_scale Int#
scale# Int#
n# where !(I# Int#
scale#) = SIZEOF_HSDOUBLE
fLOAT_SCALE :: Int# -> Int#
fLOAT_SCALE  Int#
n# = Int# -> Int# -> Int#
safe_scale Int#
scale# Int#
n# where !(I# Int#
scale#) = SIZEOF_HSFLOAT

safe_scale :: Int# -> Int# -> Int#
safe_scale :: Int# -> Int# -> Int#
safe_scale Int#
scale# Int#
n#
  | Bool -> Bool
not Bool
overflow = Int#
res#
  | Bool
otherwise    = [Char] -> Int#
forall a. HasCallStack => [Char] -> a
error ([Char] -> Int#) -> [Char] -> Int#
forall a b. (a -> b) -> a -> b
$ [Char]
"Data.Array.Base.safe_scale: Overflow; scale: "
    [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show (Int# -> Int
I# Int#
scale#) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", n: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show (Int# -> Int
I# Int#
n#)
  where
    !res# :: Int#
res# = Int#
scale# Int# -> Int# -> Int#
*# Int#
n#
    !overflow :: Bool
overflow = Int# -> Bool
isTrue# (Int#
maxN# Int# -> Int# -> Int#
`divInt#` Int#
scale# Int# -> Int# -> Int#
<# Int#
n#)
    !(I# Int#
maxN#) = Int
forall a. Bounded a => a
External instance of the constraint type Bounded Int
maxBound
{-# INLINE safe_scale #-}

-- | The index of the word which the given @Bool@ array elements falls within.
bOOL_INDEX :: Int# -> Int#
#if SIZEOF_HSWORD == 4
bOOL_INDEX i# = i# `uncheckedIShiftRA#` 5#
#elif SIZEOF_HSWORD == 8
bOOL_INDEX :: Int# -> Int#
bOOL_INDEX Int#
i# = Int#
i# Int# -> Int# -> Int#
`uncheckedIShiftRA#` Int#
6#
#endif

bOOL_BIT, bOOL_NOT_BIT :: Int# -> Word#
bOOL_BIT :: Int# -> Word#
bOOL_BIT     Int#
n# = Int# -> Word#
int2Word# Int#
1# Word# -> Int# -> Word#
`uncheckedShiftL#` (Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
n# Word# -> Word# -> Word#
`and#` Word#
mask#))
    where !(W# Word#
mask#) = SIZEOF_HSWORD * 8 - 1
bOOL_NOT_BIT :: Int# -> Word#
bOOL_NOT_BIT Int#
n# = Int# -> Word#
bOOL_BIT Int#
n# Word# -> Word# -> Word#
`xor#` Word#
mb#
    where !(W# Word#
mb#) = Word
forall a. Bounded a => a
External instance of the constraint type Bounded Word
maxBound

-----------------------------------------------------------------------------
-- Freezing

-- | Converts a mutable array (any instance of 'MArray') to an
-- immutable array (any instance of 'IArray') by taking a complete
-- copy of it.
freeze :: (Ix i, MArray a e m, IArray b e) => a i e -> m (b i e)
{-# NOINLINE [1] freeze #-}
freeze :: a i e -> m (b i e)
freeze a i e
marr = do
  (i
l,i
u) <- a i e -> m (i, i)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getBounds a i e
marr
  Int
n <- a i e -> m Int
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> m Int
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
getNumElements a i e
marr
  [e]
es <- (Int -> m e) -> [Int] -> m [e]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
External instance of the constraint type Traversable []
mapM (a i e -> Int -> m e
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> m e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray a e m
unsafeRead a i e
marr) [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]
  -- The old array and index might not be well-behaved, so we need to
  -- use the safe array creation function here.
  b i e -> m (b i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray a e m
return ((i, i) -> [e] -> b i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray b e
listArray (i
l,i
u) [e]
es)

freezeSTUArray :: STUArray s i e -> ST s (UArray i e)
freezeSTUArray :: STUArray s i e -> ST s (UArray i e)
freezeSTUArray (STUArray i
l i
u Int
n MutableByteArray# s
marr#) = STRep s (UArray i e) -> ST s (UArray i e)
forall s a. STRep s a -> ST s a
ST (STRep s (UArray i e) -> ST s (UArray i e))
-> STRep s (UArray i e) -> ST s (UArray i e)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
    case MutableByteArray# s -> Int#
forall d. MutableByteArray# d -> Int#
sizeofMutableByteArray# MutableByteArray# s
marr#  of { Int#
n# ->
    case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
n# State# s
s1#           of { (# State# s
s2#, MutableByteArray# s
marr'# #) ->
    case MutableByteArray# s -> MutableByteArray# s -> CSize -> IO (Ptr Any)
forall s a.
MutableByteArray# s -> MutableByteArray# s -> CSize -> IO (Ptr a)
memcpy_freeze MutableByteArray# s
marr'# MutableByteArray# s
marr# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num CSize
External instance of the constraint type Integral Int
fromIntegral (Int# -> Int
I# Int#
n#)) of { IO State# RealWorld -> (# State# RealWorld, Ptr Any #)
m ->
    case (State# RealWorld -> (# State# RealWorld, Ptr Any #))
-> State# s -> (# State# s, Any #)
unsafeCoerce# State# RealWorld -> (# State# RealWorld, Ptr Any #)
m State# s
s2#            of { (# State# s
s3#, Any
_ #) ->
    case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
marr'# State# s
s3# of { (# State# s
s4#, ByteArray#
arr# #) ->
    (# State# s
s4#, i -> i -> Int -> ByteArray# -> UArray i e
forall i e. i -> i -> Int -> ByteArray# -> UArray i e
UArray i
l i
u Int
n ByteArray#
arr# #) }}}}}

foreign import ccall unsafe "memcpy"
    memcpy_freeze :: MutableByteArray# s -> MutableByteArray# s -> CSize
           -> IO (Ptr a)

{-# RULES
"freeze/STArray"  freeze = ArrST.freezeSTArray
"freeze/STUArray" freeze = freezeSTUArray
    #-}

-- In-place conversion of mutable arrays to immutable ones places
-- a proof obligation on the user: no other parts of your code can
-- have a reference to the array at the point where you unsafely
-- freeze it (and, subsequently mutate it, I suspect).

{- |
   Converts an mutable array into an immutable array.  The
   implementation may either simply cast the array from
   one type to the other without copying the array, or it
   may take a full copy of the array.

   Note that because the array is possibly not copied, any subsequent
   modifications made to the mutable version of the array may be
   shared with the immutable version.  It is safe to use, therefore, if
   the mutable version is never modified after the freeze operation.

   The non-copying implementation is supported between certain pairs
   of array types only; one constraint is that the array types must
   have identical representations.  In GHC, The following pairs of
   array types have a non-copying O(1) implementation of
   'unsafeFreeze'.  Because the optimised versions are enabled by
   specialisations, you will need to compile with optimisation (-O) to
   get them.

     * 'Data.Array.IO.IOUArray' -> 'Data.Array.Unboxed.UArray'

     * 'Data.Array.ST.STUArray' -> 'Data.Array.Unboxed.UArray'

     * 'Data.Array.IO.IOArray' -> 'Data.Array.Array'

     * 'Data.Array.ST.STArray' -> 'Data.Array.Array'
-}
{-# INLINE [1] unsafeFreeze #-}
unsafeFreeze :: (Ix i, MArray a e m, IArray b e) => a i e -> m (b i e)
unsafeFreeze :: a i e -> m (b i e)
unsafeFreeze = a i e -> m (b i e)
forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
Evidence bound by a type signature of the constraint type IArray b e
Evidence bound by a type signature of the constraint type MArray a e m
Evidence bound by a type signature of the constraint type Ix i
freeze

{-# RULES
"unsafeFreeze/STArray"  unsafeFreeze = ArrST.unsafeFreezeSTArray
"unsafeFreeze/STUArray" unsafeFreeze = unsafeFreezeSTUArray
    #-}

-----------------------------------------------------------------------------
-- Thawing

-- | Converts an immutable array (any instance of 'IArray') into a
-- mutable array (any instance of 'MArray') by taking a complete copy
-- of it.
thaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e)
{-# NOINLINE [1] thaw #-}
thaw :: a i e -> m (b i e)
thaw a i e
arr = case a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
bounds a i e
arr of
  (i
l,i
u) -> do
    b i e
marr <- (i, i) -> m (b i e)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray b e m
newArray_ (i
l,i
u)
    let n :: Int
n = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
Evidence bound by a type signature of the constraint type Ix i
safeRangeSize (i
l,i
u)
    [m ()] -> m ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray b e m
External instance of the constraint type Foldable []
sequence_ [ b i e -> Int -> e -> m ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Int -> e -> m ()
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type MArray b e m
unsafeWrite b i e
marr Int
i (a i e -> Int -> e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
Evidence bound by a type signature of the constraint type Ix i
Evidence bound by a type signature of the constraint type IArray a e
unsafeAt a i e
arr Int
i)
              | Int
i <- [Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1]]
    b i e -> m (b i e)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MArray of the constraint type forall (a :: * -> * -> *) e (m :: * -> *). MArray a e m => Monad m
Evidence bound by a type signature of the constraint type MArray b e m
return b i e
marr

thawSTUArray :: UArray i e -> ST s (STUArray s i e)
thawSTUArray :: UArray i e -> ST s (STUArray s i e)
thawSTUArray (UArray i
l i
u Int
n ByteArray#
arr#) = STRep s (STUArray s i e) -> ST s (STUArray s i e)
forall s a. STRep s a -> ST s a
ST (STRep s (STUArray s i e) -> ST s (STUArray s i e))
-> STRep s (STUArray s i e) -> ST s (STUArray s i e)
forall a b. (a -> b) -> a -> b
$ \State# s
s1# ->
    case ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr#          of { Int#
n# ->
    case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
n# State# s
s1#           of { (# State# s
s2#, MutableByteArray# s
marr# #) ->
    case MutableByteArray# s -> ByteArray# -> CSize -> IO (Ptr Any)
forall s a.
MutableByteArray# s -> ByteArray# -> CSize -> IO (Ptr a)
memcpy_thaw MutableByteArray# s
marr# ByteArray#
arr# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num CSize
External instance of the constraint type Integral Int
fromIntegral (Int# -> Int
I# Int#
n#)) of { IO State# RealWorld -> (# State# RealWorld, Ptr Any #)
m ->
    case (State# RealWorld -> (# State# RealWorld, Ptr Any #))
-> State# s -> (# State# s, Any #)
unsafeCoerce# State# RealWorld -> (# State# RealWorld, Ptr Any #)
m State# s
s2#            of { (# State# s
s3#, Any
_ #) ->
    (# State# s
s3#, i -> i -> Int -> MutableByteArray# s -> STUArray s i e
forall s i e.
i -> i -> Int -> MutableByteArray# s -> STUArray s i e
STUArray i
l i
u Int
n MutableByteArray# s
marr# #) }}}}

foreign import ccall unsafe "memcpy"
    memcpy_thaw :: MutableByteArray# s -> ByteArray# -> CSize
           -> IO (Ptr a)

{-# RULES
"thaw/STArray"  thaw = ArrST.thawSTArray
"thaw/STUArray" thaw = thawSTUArray
    #-}

-- In-place conversion of immutable arrays to mutable ones places
-- a proof obligation on the user: no other parts of your code can
-- have a reference to the array at the point where you unsafely
-- thaw it (and, subsequently mutate it, I suspect).

{- |
   Converts an immutable array into a mutable array.  The
   implementation may either simply cast the array from
   one type to the other without copying the array, or it
   may take a full copy of the array.

   Note that because the array is possibly not copied, any subsequent
   modifications made to the mutable version of the array may be
   shared with the immutable version.  It is only safe to use,
   therefore, if the immutable array is never referenced again in this
   thread, and there is no possibility that it can be also referenced
   in another thread.  If you use an unsafeThaw/write/unsafeFreeze
   sequence in a multi-threaded setting, then you must ensure that
   this sequence is atomic with respect to other threads, or a garbage
   collector crash may result (because the write may be writing to a
   frozen array).

   The non-copying implementation is supported between certain pairs
   of array types only; one constraint is that the array types must
   have identical representations.  In GHC, The following pairs of
   array types have a non-copying O(1) implementation of
   'unsafeThaw'.  Because the optimised versions are enabled by
   specialisations, you will need to compile with optimisation (-O) to
   get them.

     * 'Data.Array.Unboxed.UArray' -> 'Data.Array.IO.IOUArray'

     * 'Data.Array.Unboxed.UArray' -> 'Data.Array.ST.STUArray'

     * 'Data.Array.Array'  -> 'Data.Array.IO.IOArray'

     * 'Data.Array.Array'  -> 'Data.Array.ST.STArray'
-}
{-# INLINE [1] unsafeThaw #-}
unsafeThaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e)
unsafeThaw :: a i e -> m (b i e)
unsafeThaw = a i e -> m (b i e)
forall i (a :: * -> * -> *) e (b :: * -> * -> *) (m :: * -> *).
(Ix i, IArray a e, MArray b e m) =>
a i e -> m (b i e)
Evidence bound by a type signature of the constraint type MArray b e m
Evidence bound by a type signature of the constraint type IArray a e
Evidence bound by a type signature of the constraint type Ix i
thaw

{-# INLINE unsafeThawSTUArray #-}
unsafeThawSTUArray :: UArray i e -> ST s (STUArray s i e)
unsafeThawSTUArray :: UArray i e -> ST s (STUArray s i e)
unsafeThawSTUArray (UArray i
l i
u Int
n ByteArray#
marr#) =
    STUArray s i e -> ST s (STUArray s i e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (i -> i -> Int -> MutableByteArray# s -> STUArray s i e
forall s i e.
i -> i -> Int -> MutableByteArray# s -> STUArray s i e
STUArray i
l i
u Int
n (ByteArray# -> MutableByteArray# s
unsafeCoerce# ByteArray#
marr#))

{-# RULES
"unsafeThaw/STArray"    unsafeThaw = ArrST.unsafeThawSTArray
"unsafeThaw/STUArray"   unsafeThaw = unsafeThawSTUArray
    #-}

{-# INLINE unsafeThawIOArray #-}
unsafeThawIOArray :: Arr.Array ix e -> IO (IOArray ix e)
unsafeThawIOArray :: Array ix e -> IO (IOArray ix e)
unsafeThawIOArray Array ix e
arr = ST RealWorld (IOArray ix e) -> IO (IOArray ix e)
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld (IOArray ix e) -> IO (IOArray ix e))
-> ST RealWorld (IOArray ix e) -> IO (IOArray ix e)
forall a b. (a -> b) -> a -> b
$ do
    STArray RealWorld ix e
marr <- Array ix e -> ST RealWorld (STArray RealWorld ix e)
forall i e s. Array i e -> ST s (STArray s i e)
ArrST.unsafeThawSTArray Array ix e
arr
    IOArray ix e -> ST RealWorld (IOArray ix e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (STArray RealWorld ix e -> IOArray ix e
forall i e. STArray RealWorld i e -> IOArray i e
IOArray STArray RealWorld ix e
marr)

{-# RULES
"unsafeThaw/IOArray"  unsafeThaw = unsafeThawIOArray
    #-}

thawIOArray :: Arr.Array ix e -> IO (IOArray ix e)
thawIOArray :: Array ix e -> IO (IOArray ix e)
thawIOArray Array ix e
arr = ST RealWorld (IOArray ix e) -> IO (IOArray ix e)
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld (IOArray ix e) -> IO (IOArray ix e))
-> ST RealWorld (IOArray ix e) -> IO (IOArray ix e)
forall a b. (a -> b) -> a -> b
$ do
    STArray RealWorld ix e
marr <- Array ix e -> ST RealWorld (STArray RealWorld ix e)
forall i e s. Array i e -> ST s (STArray s i e)
ArrST.thawSTArray Array ix e
arr
    IOArray ix e -> ST RealWorld (IOArray ix e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (STArray RealWorld ix e -> IOArray ix e
forall i e. STArray RealWorld i e -> IOArray i e
IOArray STArray RealWorld ix e
marr)

{-# RULES
"thaw/IOArray"  thaw = thawIOArray
    #-}

freezeIOArray :: IOArray ix e -> IO (Arr.Array ix e)
freezeIOArray :: IOArray ix e -> IO (Array ix e)
freezeIOArray (IOArray STArray RealWorld ix e
marr) = ST RealWorld (Array ix e) -> IO (Array ix e)
forall a. ST RealWorld a -> IO a
stToIO (STArray RealWorld ix e -> ST RealWorld (Array ix e)
forall s i e. STArray s i e -> ST s (Array i e)
ArrST.freezeSTArray STArray RealWorld ix e
marr)

{-# RULES
"freeze/IOArray"  freeze = freezeIOArray
    #-}

{-# INLINE unsafeFreezeIOArray #-}
unsafeFreezeIOArray :: IOArray ix e -> IO (Arr.Array ix e)
unsafeFreezeIOArray :: IOArray ix e -> IO (Array ix e)
unsafeFreezeIOArray (IOArray STArray RealWorld ix e
marr) = ST RealWorld (Array ix e) -> IO (Array ix e)
forall a. ST RealWorld a -> IO a
stToIO (STArray RealWorld ix e -> ST RealWorld (Array ix e)
forall s i e. STArray s i e -> ST s (Array i e)
ArrST.unsafeFreezeSTArray STArray RealWorld ix e
marr)

{-# RULES
"unsafeFreeze/IOArray"  unsafeFreeze = unsafeFreezeIOArray
    #-}

-- | Casts an 'STUArray' with one element type into one with a
-- different element type.  All the elements of the resulting array
-- are undefined (unless you know what you\'re doing...).

castSTUArray :: STUArray s ix a -> ST s (STUArray s ix b)
castSTUArray :: STUArray s ix a -> ST s (STUArray s ix b)
castSTUArray (STUArray ix
l ix
u Int
n MutableByteArray# s
marr#) = STUArray s ix b -> ST s (STUArray s ix b)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (ST s)
return (ix -> ix -> Int -> MutableByteArray# s -> STUArray s ix b
forall s i e.
i -> i -> Int -> MutableByteArray# s -> STUArray s i e
STUArray ix
l ix
u Int
n MutableByteArray# s
marr#)