Skip to content

Commit f845c2f

Browse files
added Ptr arrays
1 parent cb26ff6 commit f845c2f

File tree

1 file changed

+22
-3
lines changed
  • mutable-containers/src/Data/Mutable

1 file changed

+22
-3
lines changed

mutable-containers/src/Data/Mutable/Class.hs

+22-3
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,10 @@ import qualified Data.Vector.Primitive.Mutable as MPV
4646
import qualified Data.Vector.Storable.Mutable as MSV
4747
import qualified Data.Vector.Unboxed.Mutable as MUV
4848
import qualified GHC.Arr
49+
import qualified Foreign.Marshal.Array as Foreign
50+
import Foreign.Ptr (Ptr)
51+
import Foreign.Storable (Storable)
52+
import qualified Foreign.Storable as Foreign
4953

5054
-- | The parent typeclass for all mutable containers.
5155
--
@@ -73,6 +77,8 @@ instance MutableContainer (MUV.MVector s a) where
7377
type MCState (MUV.MVector s a) = s
7478
instance MutableContainer (GHC.Arr.STArray s i e) where
7579
type MCState (GHC.Arr.STArray s i e) = s
80+
instance MutableContainer (Ptr a) where
81+
type MCState (Ptr a) = PrimState IO
7682

7783
-- | Typeclass for single-cell mutable references.
7884
--
@@ -228,7 +234,7 @@ instance MPV.Prim a => MutableCollection (MPV.MVector s a) where
228234
type CollElement (MPV.MVector s a) = a
229235
newColl = MPV.new 0
230236
{-# INLINE newColl #-}
231-
instance MSV.Storable a => MutableCollection (MSV.MVector s a) where
237+
instance Storable a => MutableCollection (MSV.MVector s a) where
232238
type CollElement (MSV.MVector s a) = a
233239
newColl = MSV.new 0
234240
{-# INLINE newColl #-}
@@ -240,6 +246,10 @@ instance (GHC.Arr.Ix i, Num i) => MutableCollection (GHC.Arr.STArray s i e) wher
240246
type CollElement (GHC.Arr.STArray s i e) = e
241247
newColl = primToPrim $ GHC.Arr.newSTArray (0,0) undefined
242248
{-# INLINE newColl #-}
249+
instance Storable a => MutableCollection (Ptr a) where
250+
type CollElement (Ptr a) = a
251+
newColl = primToPrim $ Foreign.mallocArray 0
252+
{-# INLINE newColl #-}
243253

244254
-- | Containers that can be initialized with n elements.
245255
class MutableCollection c => MutableInitialSizedCollection c where
@@ -255,7 +265,7 @@ instance MPV.Prim a => MutableInitialSizedCollection (MPV.MVector s a) where
255265
type CollIndex (MPV.MVector s a) = Int
256266
newCollOfSize = MPV.new
257267
{-# INLINE newCollOfSize #-}
258-
instance MSV.Storable a => MutableInitialSizedCollection (MSV.MVector s a) where
268+
instance Storable a => MutableInitialSizedCollection (MSV.MVector s a) where
259269
type CollIndex (MSV.MVector s a) = Int
260270
newCollOfSize = MSV.new
261271
{-# INLINE newCollOfSize #-}
@@ -267,6 +277,10 @@ instance (GHC.Arr.Ix i, Num i) => MutableInitialSizedCollection (GHC.Arr.STArray
267277
type CollIndex (GHC.Arr.STArray s i e) = i
268278
newCollOfSize x = primToPrim $ GHC.Arr.newSTArray (0,x) undefined
269279
{-# INLINE newCollOfSize #-}
280+
instance Storable a => MutableInitialSizedCollection (Ptr a) where
281+
type CollIndex (Ptr a) = Int
282+
newCollOfSize = primToPrim . Foreign.mallocArray
283+
{-# INLINE newCollOfSize #-}
270284

271285
class MutableInitialSizedCollection c => MutableIndexing c where
272286
readIndex :: (PrimMonad m, PrimState m ~ MCState c) => c -> CollIndex c -> m (CollElement c)
@@ -281,7 +295,7 @@ instance MPV.Prim a => MutableIndexing (MPV.MVector s a) where
281295
{-# INLINE readIndex #-}
282296
writeIndex = MPV.write
283297
{-# INLINE writeIndex #-}
284-
instance MSV.Storable a => MutableIndexing (MSV.MVector s a) where
298+
instance Storable a => MutableIndexing (MSV.MVector s a) where
285299
readIndex = MSV.read
286300
{-# INLINE readIndex #-}
287301
writeIndex = MSV.write
@@ -296,6 +310,11 @@ instance (GHC.Arr.Ix i, Num i) => MutableIndexing (GHC.Arr.STArray s i e) where
296310
{-# INLINE readIndex #-}
297311
writeIndex c i e = primToPrim $ GHC.Arr.writeSTArray c i e
298312
{-# INLINE writeIndex #-}
313+
instance Storable a => MutableIndexing (Ptr a) where
314+
readIndex p i = primToPrim $ Foreign.peekElemOff p i
315+
{-# INLINE readIndex #-}
316+
writeIndex p i e = primToPrim $ Foreign.pokeElemOff p i e
317+
{-# INLINE writeIndex #-}
299318

300319
-- | Take a value from the front of the collection, if available.
301320
--

0 commit comments

Comments
 (0)