@@ -20,8 +20,9 @@ module Data.Mutable.Class
20
20
, MutableRef (.. )
21
21
, MutableAtomicRef (.. )
22
22
, MutableCollection (.. )
23
- , MutableInitialSizedCollection (.. )
24
- , MutableIndexing (.. )
23
+ , MutableAllocatedCollection (.. )
24
+ , CollIndex
25
+ , MutableIndexingWrite (.. )
25
26
, MutablePushFront (.. )
26
27
, MutablePushBack (.. )
27
28
, MutablePopFront (.. )
@@ -228,90 +229,85 @@ instance Monoid w => MutableCollection (MutVar s w) where
228
229
instance MutableCollection (MV. MVector s a ) where
229
230
type CollElement (MV. MVector s a ) = a
230
231
newColl = MV. new 0
231
- {-# INLINE newColl #-}
232
232
instance MPV. Prim a => MutableCollection (MPV. MVector s a ) where
233
233
type CollElement (MPV. MVector s a ) = a
234
234
newColl = MPV. new 0
235
- {-# INLINE newColl #-}
236
235
instance Storable a => MutableCollection (MSV. MVector s a ) where
237
236
type CollElement (MSV. MVector s a ) = a
238
237
newColl = MSV. new 0
239
- {-# INLINE newColl #-}
240
238
instance MUV. Unbox a => MutableCollection (MUV. MVector s a ) where
241
239
type CollElement (MUV. MVector s a ) = a
242
240
newColl = MUV. new 0
243
- {-# INLINE newColl #-}
244
241
instance (GHC.Arr. Ix i , Num i ) => MutableCollection (GHC.Arr. STArray s i e ) where
245
242
type CollElement (GHC.Arr. STArray s i e ) = e
246
243
newColl = primToPrim $ GHC.Arr. newSTArray (0 ,0 ) undefined
247
- {-# INLINE newColl #-}
248
244
instance Storable a => MutableCollection (Ptr a ) where
249
245
type CollElement (Ptr a ) = a
250
246
newColl = primToPrim $ Foreign. mallocArray 0
251
- {-# INLINE newColl #-}
252
247
253
248
-- | Containers that can be initialized with n elements.
254
- class MutableCollection c => MutableInitialSizedCollection c where
255
- type CollIndex c
249
+ type family CollIndex c
250
+
251
+ class MutableCollection c => MutableAllocatedCollection c where
256
252
newCollOfSize :: (PrimMonad m , PrimState m ~ MCState c )
257
253
=> CollIndex c
258
254
-> m c
259
- instance MutableInitialSizedCollection (MV. MVector s a ) where
260
- type CollIndex (MV. MVector s a ) = Int
255
+ type instance CollIndex (MV. MVector s a ) = Int
256
+ instance MutableAllocatedCollection (MV. MVector s a ) where
261
257
newCollOfSize = MV. new
262
258
{-# INLINE newCollOfSize #-}
263
- instance MPV. Prim a => MutableInitialSizedCollection (MPV. MVector s a ) where
264
- type CollIndex (MPV. MVector s a ) = Int
259
+ type instance CollIndex (MPV. MVector s a ) = Int
260
+ instance MPV. Prim a => MutableAllocatedCollection (MPV. MVector s a ) where
265
261
newCollOfSize = MPV. new
266
262
{-# INLINE newCollOfSize #-}
267
- instance Storable a => MutableInitialSizedCollection (MSV. MVector s a ) where
268
- type CollIndex (MSV. MVector s a ) = Int
263
+ type instance CollIndex (MSV. MVector s a ) = Int
264
+ instance Storable a => MutableAllocatedCollection (MSV. MVector s a ) where
269
265
newCollOfSize = MSV. new
270
266
{-# INLINE newCollOfSize #-}
271
- instance MUV. Unbox a => MutableInitialSizedCollection (MUV. MVector s a ) where
272
- type CollIndex (MUV. MVector s a ) = Int
267
+ type instance CollIndex (MUV. MVector s a ) = Int
268
+ instance MUV. Unbox a => MutableAllocatedCollection (MUV. MVector s a ) where
273
269
newCollOfSize = MUV. new
274
270
{-# INLINE newCollOfSize #-}
275
- instance ( GHC.Arr. Ix i , Num i ) => MutableInitialSizedCollection (GHC.Arr. STArray s i e ) where
276
- type CollIndex (GHC.Arr. STArray s i e ) = i
271
+ type instance CollIndex (GHC.Arr. STArray s i e ) = i
272
+ instance ( GHC.Arr. Ix i , Num i ) => MutableAllocatedCollection (GHC.Arr. STArray s i e ) where
277
273
newCollOfSize x = primToPrim $ GHC.Arr. newSTArray (0 ,x) undefined
278
274
{-# INLINE newCollOfSize #-}
279
- instance Storable a => MutableInitialSizedCollection (Ptr a ) where
280
- type CollIndex (Ptr a ) = Int
275
+ type instance CollIndex (Ptr a ) = Int
276
+ instance Storable a => MutableAllocatedCollection (Ptr a ) where
281
277
newCollOfSize = primToPrim . Foreign. mallocArray
282
278
{-# INLINE newCollOfSize #-}
283
279
284
- class MutableInitialSizedCollection c => MutableIndexing c where
285
- readIndex :: (PrimMonad m , PrimState m ~ MCState c ) => c -> CollIndex c -> m (CollElement c )
280
+ class MutableAllocatedCollection c => MutableIndexingWrite c where
281
+ -- readIndex :: (PrimMonad m, PrimState m ~ MCState c) => c -> CollIndex c -> m (CollElement c)
286
282
writeIndex :: (PrimMonad m , PrimState m ~ MCState c ) => c -> CollIndex c -> CollElement c -> m ()
287
- instance MutableIndexing (MV. MVector s a ) where
288
- readIndex = MV. read
289
- {-# INLINE readIndex #-}
283
+ instance MutableIndexingWrite (MV. MVector s a ) where
284
+ -- readIndex = MV.read
285
+ -- {-# INLINE readIndex #-}
290
286
writeIndex = MV. write
291
287
{-# INLINE writeIndex #-}
292
- instance MPV. Prim a => MutableIndexing (MPV. MVector s a ) where
293
- readIndex = MPV. read
294
- {-# INLINE readIndex #-}
288
+ instance MPV. Prim a => MutableIndexingWrite (MPV. MVector s a ) where
289
+ -- readIndex = MPV.read
290
+ -- {-# INLINE readIndex #-}
295
291
writeIndex = MPV. write
296
292
{-# INLINE writeIndex #-}
297
- instance Storable a => MutableIndexing (MSV. MVector s a ) where
298
- readIndex = MSV. read
299
- {-# INLINE readIndex #-}
293
+ instance Storable a => MutableIndexingWrite (MSV. MVector s a ) where
294
+ -- readIndex = MSV.read
295
+ -- {-# INLINE readIndex #-}
300
296
writeIndex = MSV. write
301
297
{-# INLINE writeIndex #-}
302
- instance MUV. Unbox a => MutableIndexing (MUV. MVector s a ) where
303
- readIndex = MUV. read
304
- {-# INLINE readIndex #-}
298
+ instance MUV. Unbox a => MutableIndexingWrite (MUV. MVector s a ) where
299
+ -- readIndex = MUV.read
300
+ -- {-# INLINE readIndex #-}
305
301
writeIndex = MUV. write
306
302
{-# INLINE writeIndex #-}
307
- instance (GHC.Arr. Ix i , Num i ) => MutableIndexing (GHC.Arr. STArray s i e ) where
308
- readIndex c i = primToPrim $ GHC.Arr. readSTArray c i
309
- {-# INLINE readIndex #-}
303
+ instance (GHC.Arr. Ix i , Num i ) => MutableIndexingWrite (GHC.Arr. STArray s i e ) where
304
+ -- readIndex c i = primToPrim $ GHC.Arr.readSTArray c i
305
+ -- {-# INLINE readIndex #-}
310
306
writeIndex c i e = primToPrim $ GHC.Arr. writeSTArray c i e
311
307
{-# INLINE writeIndex #-}
312
- instance Storable a => MutableIndexing (Ptr a ) where
313
- readIndex p i = primToPrim $ Foreign. peekElemOff p i
314
- {-# INLINE readIndex #-}
308
+ instance Storable a => MutableIndexingWrite (Ptr a ) where
309
+ -- readIndex p i = primToPrim $ Foreign.peekElemOff p i
310
+ -- {-# INLINE readIndex #-}
315
311
writeIndex p i e = primToPrim $ Foreign. pokeElemOff p i e
316
312
{-# INLINE writeIndex #-}
317
313
0 commit comments