{-# LANGUAGE BangPatterns, CPP, RankNTypes, MagicHash, UnboxedTuples, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, DeriveDataTypeable, UnliftedFFITypes #-}{-# LANGUAGE 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.-------------------------------------------------------------------------------moduleData.Array.BasewhereimportControl.Monad.ST.Lazy(strictToLazyST)importqualifiedControl.Monad.ST.LazyasLazy(ST)importData.Ix(Ix,range,index,rangeSize)importForeign.C.TypesimportForeign.StablePtrimportData.CharimportGHC.Arr(STArray)importqualifiedGHC.ArrasArrimportqualifiedGHC.ArrasArrSTimportGHC.ST(ST(..),runST)importGHC.Base(IO(..),divInt#)importGHC.ExtsimportGHC.Ptr(nullPtr,nullFunPtr)importGHC.Stable(StablePtr(..))importGHC.Int(Int8(..),Int16(..),Int32(..),Int64(..))importGHC.Word(Word8(..),Word16(..),Word32(..),Word64(..))importGHC.IO(stToIO)importGHC.IOArray(IOArray(..),newIOArray,unsafeReadIOArray,unsafeWriteIOArray)importData.Typeable#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.
-}classIArray a e where-- | Extracts the bounds of an immutable arraybounds ::Ixi =>a i e ->(i ,i )numElements ::Ixi =>a i e ->IntunsafeArray ::Ixi =>(i ,i )->[(Int,e )]->a i e unsafeAt ::Ixi =>a i e ->Int->e unsafeReplace ::Ixi =>a i e ->[(Int,e )]->a i e unsafeAccum ::Ixi =>(e ->e' ->e )->a i e ->[(Int,e' )]->a i e unsafeAccumArray ::Ixi =>(e ->e' ->e )->e ->(i ,i )->[(Int,e' )]->a i e unsafeReplace arr ies =runST(unsafeReplaceST arr ies >>=unsafeFreeze )unsafeAccum f arr ies =runST(unsafeAccumST f arr ies >>=unsafeFreeze )unsafeAccumArray f e lu ies =runST(unsafeAccumArrayST f e lu ies >>=unsafeFreeze ){-# INLINEsafeRangeSize#-}safeRangeSize::Ixi =>(i ,i )->IntsafeRangeSize (l ,u )=letr =rangeSize(l ,u )inifr <0thenerror"Negative range size"elser {-# INLINEsafeIndex#-}safeIndex::Ixi =>(i ,i )->Int->i ->IntsafeIndex (l ,u )n i =leti' =index(l ,u )i inif(0<=i' )&&(i' <n )theni' elseerror("Error in array index; "++showi' ++" not in range [0.."++shown ++")"){-# INLINEunsafeReplaceST#-}unsafeReplaceST::(IArray a e ,Ixi )=>a i e ->[(Int,e )]->STs (STArrays i e )unsafeReplaceST arr ies =domarr <-thaw arr sequence_[unsafeWrite marr i e |(i ,e )<-ies ]returnmarr {-# INLINEunsafeAccumST#-}unsafeAccumST::(IArray a e ,Ixi )=>(e ->e' ->e )->a i e ->[(Int,e' )]->STs (STArrays i e )unsafeAccumST f arr ies =domarr <-thaw arr sequence_[doold <-unsafeRead marr i unsafeWrite marr i (f old new )|(i ,new )<-ies ]returnmarr {-# INLINEunsafeAccumArrayST#-}unsafeAccumArrayST::Ixi =>(e ->e' ->e )->e ->(i ,i )->[(Int,e' )]->STs (STArrays i e )unsafeAccumArrayST f e (l ,u )ies =domarr <-newArray (l ,u )e sequence_[doold <-unsafeRead marr i unsafeWrite marr i (f old new )|(i ,new )<-ies ]returnmarr {-# INLINEarray#-}{-| 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 ,Ixi )=>(i ,i )-- ^ bounds of the array: (lowest,highest)->[(i ,e )]-- ^ list of associations->a i e array (l ,u )ies =letn =safeRangeSize (l ,u )inunsafeArray (l ,u )[(safeIndex (l ,u )n i ,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 ,Ixi )=>(i ,i )->[e ]->a i e listArray (l ,u )es =letn =safeRangeSize (l ,u )inunsafeArray (l ,u )(zip[0..n -1]es ){-# INLINElistArrayST#-}listArrayST::Ixi =>(i ,i )->[e ]->STs (STArrays i e )listArrayST (l ,u )es =domarr <-newArray_ (l ,u )letn =safeRangeSize (l ,u )letfillFromList i xs |i ==n =return()|otherwise=casexs of[]->return()y :ys ->unsafeWrite marr i y >>fillFromList (i +1)ys fillFromList 0es returnmarr {-# RULES"listArray/Array"listArray=\lues->runST(listArraySTlues>>=ArrST.unsafeFreezeSTArray)#-}{-# INLINElistUArrayST#-}listUArrayST::(MArray(STUArrays)e(STs),Ixi)=>(i ,i )->[e ]->STs(STUArraysie)listUArrayST(l,u)es=domarr <-newArray_(l,u)letn=safeRangeSize(l,u)letfillFromListi xs |i==n=return()|otherwise=casexsof[]->return()y:ys->unsafeWritemarriy>>fillFromList(i+1)ysfillFromList0esreturn 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.typeListUArraye=foralli.Ixi=>(i,i)->[e]->UArrayie{-# RULES"listArray/UArray/Bool"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayBool"listArray/UArray/Char"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayChar"listArray/UArray/Int"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayInt"listArray/UArray/Word"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayWord"listArray/UArray/Ptr"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArray(Ptra)"listArray/UArray/FunPtr"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArray(FunPtra)"listArray/UArray/Float"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayFloat"listArray/UArray/Double"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayDouble"listArray/UArray/StablePtr"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArray(StablePtra)"listArray/UArray/Int8"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayInt8"listArray/UArray/Int16"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayInt16"listArray/UArray/Int32"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayInt32"listArray/UArray/Int64"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayInt64"listArray/UArray/Word8"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayWord8"listArray/UArray/Word16"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayWord16"listArray/UArray/Word32"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayWord32"listArray/UArray/Word64"listArray=(\lues->runST(listUArraySTlues>>=unsafeFreezeSTUArray))::ListUArrayWord64#-}{-# INLINE(!)#-}-- | Returns the element of an immutable array at the specified index.(!)::(IArrayae,Ixi)=>aie->i->e(!)arri=caseboundsarrof(l ,u )->unsafeAtarr$safeIndex(l,u)(numElementsarr)i{-# INLINEindices#-}-- | Returns a list of all the valid indices in an array.indices::(IArrayae,Ixi)=>aie->[i]indicesarr=caseboundsarrof(l,u)->range(l,u){-# INLINEelems#-}-- | Returns a list of all the elements of an array, in the same order-- as their indices.elems::(IArrayae,Ixi)=>aie->[e]elemsarr=[unsafeAtarri|i<-[0..numElementsarr-1]]{-# INLINEassocs#-}-- | Returns the contents of an array as a list of associations.assocs::(IArrayae,Ixi)=>aie->[(i,e)]assocsarr=caseboundsarrof(l,u)->[(i ,arr!i)|i<-range(l,u )]{-# INLINEaccumArray#-}{-|
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::(IArrayae,Ixi)=>(e->e'->e)-- ^ An accumulating function->e-- ^ A default element->(i ,i)-- ^ The bounds of the array->[(i,e')]-- ^ List of associations->aie-- ^ Returns: the arrayaccumArrayfinitialValue(l,u)ies=letn=safeRangeSize(l,u)inunsafeAccumArrayf initialValue(l,u)[(safeIndex(l,u)ni,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.
-}(//)::(IArrayae,Ixi)=>aie->[(i,e)]->aiearr//ies=caseboundsarrof(l,u)->unsafeReplacearr[(safeIndex(l,u)(numElementsarr)i,e)|(i,e)<-ies]{-# INLINEaccum#-}{-|
@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::(IArrayae,Ixi)=>(e->e'->e)->aie->[(i,e')]->aieaccumfarries=caseboundsarrof(l,u)->letn =numElementsarrinunsafeAccumf arr [(safeIndex(l,u)ni,e)|(i,e)<-ies]{-# INLINEamap#-}-- | Returns a new array derived from the original array by applying a-- function to each of the elements.amap::(IArrayae',IArrayae,Ixi)=>(e'->e)->aie'->aieamapfarr=caseboundsarrof(l,u)->letn=numElementsarrinunsafeArray(l,u)[(i,f(unsafeAtarri))|i<-[0..n-1]]{-# INLINEixmap#-}-- | Returns a new array derived from the original array by applying a-- function to each of the indices.ixmap::(IArrayae,Ixi,Ixj)=>(i,i)->(i->j)->aje->aieixmap(l,u)farr=array(l ,u )[(i,arr!fi)|i<-range(l,u)]------------------------------------------------------------------------------- Normal polymorphic arraysinstanceIArrayArr.Arrayewhere{-# INLINEbounds#-}bounds=Arr.bounds{-# INLINEnumElements#-}numElements=Arr.numElements{-# INLINEunsafeArray#-}unsafeArray =Arr.unsafeArray{-# INLINEunsafeAt#-}unsafeAt =Arr.unsafeAt{-# INLINEunsafeReplace#-}unsafeReplace=Arr.unsafeReplace{-# INLINEunsafeAccum#-}unsafeAccum =Arr.unsafeAccum{-# INLINEunsafeAccumArray#-}unsafeAccumArray=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").--dataUArrayie=UArray!i!i!IntByteArray#derivingTypeable-- There are class-based invariants on both parameters. See also #9220.typeroleUArraynominalnominal{-# INLINEunsafeArrayUArray#-}unsafeArrayUArray::(MArray(STUArrays)e(STs),Ixi)=>(i,i)->[(Int,e)]->e->STs(UArrayie)unsafeArrayUArray(l,u)ies default_elem=domarr<-newArray(l ,u )default_elemsequence_ [unsafeWritemarri e |(i ,e)<-ies]unsafeFreezeSTUArraymarr{-# INLINEunsafeFreezeSTUArray#-}unsafeFreezeSTUArray::STUArraysie->STs(UArrayie)unsafeFreezeSTUArray(STUArraylunmarr#)=ST$\s1#->caseunsafeFreezeByteArray#marr#s1#of{(#s2# ,arr##)->(#s2# ,UArray l un arr# #)}{-# INLINEunsafeReplaceUArray#-}unsafeReplaceUArray::(MArray(STUArrays)e(STs),Ixi)=>UArrayie->[(Int,e)]->STs(UArrayie)unsafeReplaceUArrayarries =domarr<-thawSTUArrayarr sequence_ [unsafeWritemarrie|(i,e)<-ies]unsafeFreezeSTUArraymarr{-# INLINEunsafeAccumUArray#-}unsafeAccumUArray::(MArray(STUArrays)e(STs),Ixi)=>(e->e'->e)->UArrayie->[(Int,e')]->STs(UArrayie)unsafeAccumUArrayfarries =domarr<-thawSTUArrayarrsequence_ [doold<-unsafeReadmarriunsafeWritemarri(foldnew)|(i,new)<-ies ]unsafeFreezeSTUArraymarr {-# INLINEunsafeAccumArrayUArray#-}unsafeAccumArrayUArray::(MArray(STUArrays)e(STs),Ixi)=>(e->e'->e)->e->(i,i)->[(Int,e')]->STs(UArrayie)unsafeAccumArrayUArrayfinitialValue(l ,u )ies=domarr<-newArray(l,u)initialValuesequence_ [doold <-unsafeRead marri unsafeWritemarr i (f oldnew)|(i,new)<-ies ]unsafeFreezeSTUArraymarr {-# INLINEeqUArray#-}eqUArray::(IArrayUArraye,Ixi,Eqe)=>UArrayie->UArrayie->BooleqUArrayarr1@(UArrayl1u1n1_)arr2@(UArrayl2u2n2_)=ifn1==0thenn2 == 0elsel1 ==l2 &&u1 == u2 && and[unsafeAtarr1i==unsafeAtarr2i|i<-[0..n1-1]]{-# INLINE[1]cmpUArray#-}cmpUArray::(IArrayUArraye,Ixi,Orde)=>UArrayie->UArrayie->OrderingcmpUArrayarr1arr2=compare(assocsarr1)(assocsarr2){-# INLINEcmpIntUArray#-}cmpIntUArray::(IArrayUArraye,Orde)=>UArrayInte->UArrayInte->OrderingcmpIntUArrayarr1@(UArrayl1u1n1_)arr2@(UArrayl2u2n2_)=ifn1==0thenifn2== 0thenEQelseLT elseifn2 == 0thenGT elsecasecomparel1l2ofEQ->foldrcmp(compareu1u2)[0..(n1`min`n2)-1]other->otherwherecmpi rest=casecompare(unsafeAtarr1i)(unsafeAtarr2i)ofEQ->restother->other{-# RULES"cmpUArray/Int"cmpUArray=cmpIntUArray#-}------------------------------------------------------------------------------- Showing IArrays{-# SPECIALISEshowsIArray::(IArrayUArraye,Ixi,Showi,Showe)=>Int->UArrayie->ShowS#-}showsIArray::(IArrayae,Ixi,Showi,Showe)=>Int->aie->ShowSshowsIArraypa=showParen(p>9)$showString"array ".shows (boundsa).showChar' '.shows(assocsa)------------------------------------------------------------------------------- Flat unboxed arrays: instancesinstanceIArrayUArrayBoolwhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluiesFalse){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=isTrue#((indexWordArray#arr#(bOOL_INDEX i# )`and#`bOOL_BITi#)`neWord#`int2Word#0#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayCharwhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies'0円'){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=C#(indexWideCharArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayIntwhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=I#(indexIntArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayWordwhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=W#(indexWordArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArray(Ptra)where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluiesnullPtr){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=Ptr(indexAddrArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArray(FunPtra)where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluiesnullFunPtr){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=FunPtr(indexAddrArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayFloatwhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=F#(indexFloatArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayDoublewhere{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=D#(indexDoubleArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArray(StablePtra)where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluiesnullStablePtr){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=StablePtr(indexStablePtrArray#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)-- bogus StablePtr value for initialising a UArray of StablePtr.nullStablePtr::StablePtra nullStablePtr=StablePtr(unsafeCoerce#0#)instanceIArrayUArrayInt8where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=I8#(indexInt8Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayInt16where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=I16#(indexInt16Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayInt32where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=I32#(indexInt32Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayInt64where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=I64#(indexInt64Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayWord8where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=W8#(indexWord8Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayWord16where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=W16#(indexWord16Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayWord32where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=W32#(indexWord32Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instanceIArrayUArrayWord64where{-# INLINEbounds#-}bounds(UArraylu__)=(l,u){-# INLINEnumElements#-}numElements(UArray__n_)=n{-# INLINEunsafeArray#-}unsafeArrayluies=runST(unsafeArrayUArrayluies0){-# INLINEunsafeAt#-}unsafeAt(UArray___arr#)(I#i#)=W64#(indexWord64Array#arr#i#){-# INLINEunsafeReplace#-}unsafeReplacearries=runST(unsafeReplaceUArrayarries){-# INLINEunsafeAccum#-}unsafeAccumfarries=runST(unsafeAccumUArrayfarries){-# INLINEunsafeAccumArray#-}unsafeAccumArrayfinitialValueluies=runST(unsafeAccumArrayUArrayfinitialValueluies)instance(Ixix,Eqe,IArrayUArraye)=>Eq(UArrayixe)where(== )=eqUArray instance(Ixix ,Orde,IArrayUArraye)=>Ord(UArrayixe)wherecompare=cmpUArrayinstance(Ixix ,Showix,Show e ,IArrayUArraye)=>Show(UArrayixe)whereshowsPrec=showsIArray------------------------------------------------------------------------------- Mutable arrays{-# NOINLINEarrEleBottom#-}arrEleBottom::aarrEleBottom=error"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(Monadm)=>MArrayaemwhere-- | Returns the bounds of the arraygetBounds::Ix i=>a ie->m(i,i)-- | Returns the number of elements in the arraygetNumElements::Ixi=>aie->mInt-- | Builds a new array, with every element initialised to the supplied-- value.newArray::Ixi=>(i,i)->e->m(aie)-- | 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_::Ixi=>(i,i)->m(aie)-- | Builds a new array, with every element initialised to an undefined-- value.unsafeNewArray_::Ixi=>(i,i)->m(aie)unsafeRead::Ixi=>aie->Int->meunsafeWrite ::Ixi=>aie->Int->e ->m(){-# INLINEnewArray#-}-- 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(l,u)initialValue=doletn=safeRangeSize(l,u)marr<-unsafeNewArray_(l,u)sequence_[unsafeWrite marriinitialValue|i<-[0..n-1]]returnmarr{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=newArray(l,u)arrEleBottom{-# INLINEnewArray_#-}newArray_ (l ,u )=newArray(l ,u )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.instanceMArrayIOArrayeIOwhere{-# INLINEgetBounds#-}getBounds(IOArraymarr)=stToIO$getBoundsmarr{-# INLINEgetNumElements#-}getNumElements(IOArraymarr)=stToIO$getNumElementsmarrnewArray =newIOArrayunsafeRead=unsafeReadIOArrayunsafeWrite =unsafeWriteIOArray{-# INLINEnewListArray#-}-- | 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::(MArrayaem,Ixi)=>(i,i)->[e]->m(aie)newListArray(l,u)es=domarr<-newArray_(l,u)letn=safeRangeSize(l,u)letfillFromListixs|i==n=return()|otherwise=casexsof[]->return()y :ys ->unsafeWritemarriy>>fillFromList(i+1)ysfillFromList0esreturnmarr{-# INLINEreadArray#-}-- | Read an element from a mutable arrayreadArray::(MArrayaem,Ixi)=>aie->i->mereadArraymarri=do(l,u)<-getBoundsmarrn<-getNumElementsmarrunsafeReadmarr(safeIndex(l,u)ni){-# INLINEwriteArray#-}-- | Write an element in a mutable arraywriteArray::(MArrayaem,Ixi)=>aie->i->e->m()writeArraymarrie=do(l,u)<-getBoundsmarrn<-getNumElementsmarrunsafeWritemarr(safeIndex(l,u)ni)e{-# INLINEgetElems#-}-- | Return a list of all the elements of a mutable arraygetElems::(MArrayaem,Ixi)=>aie->m[e]getElemsmarr=do(_l,_u)<-getBoundsmarrn<-getNumElementsmarrsequence[unsafeReadmarri|i<-[0..n-1]]{-# INLINEgetAssocs#-}-- | Return a list of all the associations of a mutable array, in-- index order.getAssocs::(MArrayaem,Ixi)=>aie->m[(i,e)]getAssocsmarr=do(l,u)<-getBoundsmarrn<-getNumElementsmarrsequence[doe<-unsafeReadmarr(safeIndex(l,u)ni);return(i,e)|i <-range(l,u)]{-# INLINEmapArray#-}-- | Constructs a new array derived from the original array by applying a-- function to each of the elements.mapArray::(MArrayae'm,MArrayaem,Ixi)=>(e'->e)->aie'->m(aie)mapArrayfmarr=do(l,u)<-getBoundsmarrn<-getNumElementsmarrmarr' <-newArray_(l,u)sequence_[doe <-unsafeReadmarriunsafeWritemarr'i(fe)|i <-[0..n-1]]returnmarr'{-# INLINEmapIndices#-}-- | Constructs a new array derived from the original array by applying a-- function to each of the indices.mapIndices::(MArrayaem,Ixi,Ixj)=>(i,i)->(i->j)->aje->m(aie)mapIndices(l',u')fmarr=domarr'<-newArray_(l',u')n'<-getNumElementsmarr'sequence_[doe<-readArraymarr(fi')unsafeWritemarr'(safeIndex(l',u')n'i')e|i' <-range(l',u')]returnmarr'------------------------------------------------------------------------------- Polymorphic non-strict mutable arrays (ST monad)instanceMArray(STArrays)e(STs)where{-# INLINEgetBounds#-}getBoundsarr=return$!ArrST.boundsSTArrayarr{-# INLINEgetNumElements#-}getNumElementsarr=return$!ArrST.numElementsSTArrayarr{-# INLINEnewArray#-}newArray=ArrST.newSTArray{-# INLINEunsafeRead#-}unsafeRead=ArrST.unsafeReadSTArray{-# INLINEunsafeWrite#-}unsafeWrite=ArrST.unsafeWriteSTArrayinstanceMArray(STArrays)e(Lazy.STs)where{-# INLINEgetBounds#-}getBoundsarr=strictToLazyST(return$!ArrST.boundsSTArrayarr){-# INLINEgetNumElements#-}getNumElementsarr=strictToLazyST(return$!ArrST.numElementsSTArrayarr){-# INLINEnewArray#-}newArray(l,u)e=strictToLazyST(ArrST.newSTArray(l,u)e){-# INLINEunsafeRead#-}unsafeReadarri=strictToLazyST(ArrST.unsafeReadSTArrayarri){-# INLINEunsafeWrite#-}unsafeWritearrie=strictToLazyST(ArrST.unsafeWriteSTArrayarrie)------------------------------------------------------------------------------- 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.dataSTUArraysie=STUArray!i!i!Int(MutableByteArray#s)derivingTypeable-- The "ST" parameter must be nominal for the safety of the ST trick.-- The other parameters have class constraints. See also #9220.typeroleSTUArraynominalnominalnominalinstanceEq(STUArraysie)whereSTUArray___arr1#==STUArray___arr2#=isTrue#(sameMutableByteArray#arr1#arr2#){-# INLINEunsafeNewArraySTUArray_#-}unsafeNewArraySTUArray_::Ixi=>(i,i)->(Int#->Int#)->STs(STUArraysie)unsafeNewArraySTUArray_(l,u)elemsToBytes=caserangeSize(l,u)ofn@(I#n#)->ST $ \s1# ->casenewByteArray#(elemsToBytesn#)s1#of(#s2#,marr##)->(#s2#,STUArraylunmarr##)instanceMArray(STUArrays)Bool(STs)where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEnewArray#-}newArray(l,u)initialValue=ST$\s1#->casesafeRangeSize(l,u)of{n@(I#n#)->casebOOL_SCALEn#of{nbytes#->casenewByteArray#nbytes#s1#of{(#s2#,marr##)->casesetByteArray# marr#0#nbytes#e#s2#of{s3#->(#s3#,STUArrayl unmarr##)}}}}where!(I#e#)=ifinitialValuethen0xffelse0x0{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)bOOL_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBoundsFalse{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWordArray#marr# (bOOL_INDEXi#)s1#of{(#s2#,e##)->(#s2#,isTrue#((e#`and#`bOOL_BITi#)`neWord#`int2Word#0#)::Bool#)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I# i# )e =ST $\s1#->casebOOL_INDEXi#of{j# ->casereadWordArray#marr#j#s1#of{(#s2#,old##)->caseifethenold#`or#`bOOL_BITi# elseold# `and#`bOOL_NOT_BITi#of{e#->casewriteWordArray#marr#j#e# s2#of{s3#->(#s3#,()#)}}}}instanceMArray(STUArrays)Char (ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale4#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds(chr0){-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWideCharArray#marr#i# s1# of{(#s2#,e##)->(#s2#,C#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___marr# )(I#i#)(C#e#)=ST$\s1#->casewriteWideCharArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Int(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)wORD_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadIntArray#marr# i#s1# of{(#s2#,e##)->(#s2#,I#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I#i#)(I# e#)=ST$\s1#->casewriteIntArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Word (STs )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)wORD_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWordArray#marr# i#s1# of{(#s2#,e##)->(#s2#,W#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I#i#)(W#e#)=ST$\s1#->casewriteWordArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)(Ptr a)(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)wORD_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBoundsnullPtr{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadAddrArray#marr# i#s1# of{(#s2#,e##)->(#s2#,Ptre##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I#i#)(Ptre#)=ST$\s1#->casewriteAddrArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)(FunPtra)(ST s)where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)wORD_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBoundsnullFunPtr{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadAddrArray#marr# i#s1# of{(#s2#,e##)->(#s2#,FunPtre##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I#i#)(FunPtre#)=ST$\s1#->casewriteAddrArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Float (STs )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)fLOAT_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadFloatArray#marr# i# s1# of{(#s2#,e##)->(#s2#,F#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I#i#)(F#e# )=ST$\s1#->casewriteFloatArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Double(STs )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)dOUBLE_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadDoubleArray#marr#i# s1# of{(#s2#,e##)->(#s2#,D#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I# i#)(D#e# )=ST$\s1#->casewriteDoubleArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)(StablePtra )(ST s)where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)wORD_SCALE{-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds(castPtrToStablePtrnullPtr){-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadStablePtrArray#marr#i# s1#of{(#s2#,e##)->(#s2#,StablePtre##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___marr#)(I#i# )(StablePtre#)=ST$\s1#->casewriteStablePtrArray#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Int8(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(\x->x){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadInt8Array#marr# i#s1# of{(#s2#,e##)->(#s2#,I8#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray__ _ marr#)(I#i#)(I8#e#)=ST$\s1#->casewriteInt8Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Int16 (STs )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale2#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadInt16Array#marr# i# s1# of{(#s2#,e##)->(#s2#,I16#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I#i#)(I16#e#)=ST$\s1#->casewriteInt16Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Int32(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale4#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadInt32Array#marr# i# s1# of{(#s2#,e##)->(#s2#,I32#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I#i#)(I32#e#)=ST$\s1#->casewriteInt32Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Int64(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale8#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadInt64Array#marr# i# s1# of{(#s2#,e##)->(#s2#,I64#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I#i#)(I64#e#)=ST$\s1#->casewriteInt64Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Word8(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(\x->x){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWord8Array#marr# i# s1# of{(#s2#,e##)->(#s2#,W8#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I#i#)(W8#e#)=ST$\s1#->casewriteWord8Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Word16(STs )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale2#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWord16Array#marr#i# s1# of{(#s2#,e##)->(#s2#,W16#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I# i#)(W16#e#)=ST$\s1#->casewriteWord16Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Word32(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale4#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWord32Array#marr#i# s1# of{(#s2#,e##)->(#s2#,W32#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I# i#)(W32#e#)=ST$\s1#->casewriteWord32Array#marr#i#e#s1#of{s2#->(#s2#,()#)}instanceMArray(STUArrays)Word64(ST s )where{-# INLINEgetBounds#-}getBounds(STUArraylu__)=return(l,u){-# INLINEgetNumElements#-}getNumElements(STUArray__n_)=returnn{-# INLINEunsafeNewArray_#-}unsafeNewArray_(l,u)=unsafeNewArraySTUArray_(l,u)(safe_scale8#){-# INLINEnewArray_#-}newArray_arrBounds=newArrayarrBounds0{-# INLINEunsafeRead#-}unsafeRead(STUArray___marr#)(I#i#)=ST$\s1#->casereadWord64Array#marr#i# s1# of{(#s2#,e##)->(#s2#,W64#e##)}{-# INLINEunsafeWrite#-}unsafeWrite(STUArray___ marr#)(I# i#)(W64#e#)=ST$\s1#->casewriteWord64Array#marr#i#e#s1#of{s2#->(#s2#,()#)}------------------------------------------------------------------------------- Translation between elements and bytesbOOL_SCALE,wORD_SCALE,dOUBLE_SCALE,fLOAT_SCALE::Int#->Int#bOOL_SCALEn#=-- + 7 to handle case where n is not divisible by 8(n#+#7#)`uncheckedIShiftRA#`3#wORD_SCALE n#=safe_scalescale#n#where!(I#scale#)=SIZEOF_HSWORDdOUBLE_SCALEn#=safe_scalescale#n#where!(I#scale#)=SIZEOF_HSDOUBLEfLOAT_SCALEn#=safe_scalescale#n#where!(I#scale#)=SIZEOF_HSFLOATsafe_scale ::Int#->Int# ->Int# safe_scale scale#n# |notoverflow=res#|otherwise=error$"Data.Array.Base.safe_scale: Overflow; scale: "++ show(I# scale#)++", n: "++show(I#n#)where!res#=scale#*#n#!overflow=isTrue#(maxN#`divInt#`scale#<#n#)!(I#maxN#)=maxBound{-# INLINEsafe_scale#-}-- | The index of the word which the given @Bool@ array elements falls within.bOOL_INDEX::Int#->Int##ifSIZEOF_HSWORD==4bOOL_INDEXi#=i#`uncheckedIShiftRA#`5##elifSIZEOF_HSWORD==8bOOL_INDEXi#=i#`uncheckedIShiftRA#`6##endifbOOL_BIT ,bOOL_NOT_BIT::Int#->Word#bOOL_BITn#=int2Word#1#`uncheckedShiftL#`(word2Int#(int2Word#n#`and#`mask#))where!(W#mask#)=SIZEOF_HSWORD*8-1bOOL_NOT_BITn#=bOOL_BITn#`xor#`mb#where!(W#mb#)=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::(Ixi,MArrayaem,IArraybe)=>aie->m(bie){-# NOINLINE[1]freeze#-}freezemarr=do(l,u)<-getBoundsmarrn<-getNumElementsmarres <-mapM(unsafeReadmarr)[0..n-1]-- The old array and index might not be well-behaved, so we need to-- use the safe array creation function here.return(listArray(l ,u )es )#if__GLASGOW_HASKELL__>=711freezeSTUArray::STUArrays ie->STs(UArrayie)#elsefreezeSTUArray::Ixi=>STUArraysie->STs(UArrayie)#endiffreezeSTUArray(STUArraylunmarr#)=ST$\s1#->casesizeofMutableByteArray#marr#of{n#->casenewByteArray#n#s1#of{(#s2#,marr'##)->casememcpy_freezemarr'#marr#(fromIntegral(I#n#))of{IOm->caseunsafeCoerce#ms2#of{(#s3#,_#)->caseunsafeFreezeByteArray#marr'#s3#of{(#s4#,arr##)->(#s4#,UArray l u n arr# #)}}}}}foreignimportccallunsafe"memcpy"memcpy_freeze::MutableByteArray#s->MutableByteArray#s->CSize->IO(Ptra){-# 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::(Ixi,MArrayaem,IArraybe)=>aie->m(bie)unsafeFreeze=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::(Ixi,IArrayae,MArraybem)=>aie->m(bie){-# NOINLINE[1]thaw#-}thawarr=caseboundsarrof(l,u)->domarr<-newArray_(l,u)letn=safeRangeSize(l ,u )sequence_[unsafeWritemarri(unsafeAtarri)|i <-[0..n-1]]returnmarr#if__GLASGOW_HASKELL__>=711thawSTUArray::UArray i e ->ST s (STUArray s i e )#elsethawSTUArray::Ixi=>UArrayie->STs(STUArraysie)#endifthawSTUArray(UArraylunarr#)=ST$\s1#->casesizeofByteArray#arr#of{n#->casenewByteArray#n#s1#of{(#s2#,marr##)->casememcpy_thawmarr#arr#(fromIntegral(I#n#))of{IOm->caseunsafeCoerce#ms2#of{(#s3#,_#)->(#s3# ,STUArrayl u n marr##)}}}}foreignimportccallunsafe"memcpy"memcpy_thaw::MutableByteArray#s->ByteArray#->CSize->IO(Ptra){-# 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::(Ixi,IArrayae,MArraybem)=>aie->m(bie)unsafeThaw=thaw{-# INLINEunsafeThawSTUArray#-}#if__GLASGOW_HASKELL__>=711unsafeThawSTUArray::UArrayie->STs(STUArraysie)#elseunsafeThawSTUArray::Ixi=>UArrayie->STs(STUArraysie)#endifunsafeThawSTUArray(UArraylunmarr#)=return(STUArraylun(unsafeCoerce#marr#)){-# RULES"unsafeThaw/STArray"unsafeThaw=ArrST.unsafeThawSTArray"unsafeThaw/STUArray"unsafeThaw=unsafeThawSTUArray#-}{-# INLINEunsafeThawIOArray#-}#if__GLASGOW_HASKELL__>=711unsafeThawIOArray::Arr.Arrayix e->IO(IOArrayixe)#elseunsafeThawIOArray::Ixix=>Arr.Arrayixe->IO(IOArrayixe)#endifunsafeThawIOArrayarr=stToIO$domarr<-ArrST.unsafeThawSTArrayarrreturn(IOArraymarr){-# RULES"unsafeThaw/IOArray"unsafeThaw=unsafeThawIOArray#-}#if__GLASGOW_HASKELL__>=711thawIOArray::Arr.Arrayixe->IO(IOArrayixe)#elsethawIOArray::Ixix=>Arr.Arrayixe->IO(IOArrayixe)#endifthawIOArrayarr=stToIO$domarr<-ArrST.thawSTArrayarrreturn(IOArraymarr){-# RULES"thaw/IOArray"thaw=thawIOArray#-}# if__GLASGOW_HASKELL__>=711freezeIOArray::IOArrayixe->IO(Arr.Arrayixe)#elsefreezeIOArray::Ixix=>IOArrayixe->IO(Arr.Arrayixe)#endiffreezeIOArray(IOArraymarr )=stToIO(ArrST.freezeSTArraymarr){-# RULES"freeze/IOArray"freeze=freezeIOArray#-}{-# INLINEunsafeFreezeIOArray#-}#if__GLASGOW_HASKELL__>=711unsafeFreezeIOArray::IOArrayixe->IO(Arr.Arrayixe)# elseunsafeFreezeIOArray::Ixix=>IOArrayixe->IO(Arr.Arrayixe)#endifunsafeFreezeIOArray(IOArraymarr )=stToIO(ArrST.unsafeFreezeSTArraymarr){-# 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 ::STUArraysixa ->STs(STUArraysixb)castSTUArray(STUArraylunmarr#)=return(STUArraylunmarr#)

AltStyle によって変換されたページ (->オリジナル) /