let's say I've got the following type :
data MyType = Constructor0 | Constructor1 | Constructor2
deriving (Eq,Show,Enum)
Is there a way to create one of such instances :
MArray (STUArray s) MyType (ST s)
MArray IOUarray MyType IO
For the moment I store everything as Word8 and I make conversion with (wrapped) fromEnum/toEnum, but it doesn't feel right. I need strictness and unboxing because I'm using a large data structure (>1.2Go) in memory, and I can't load it lazily. If I don't find any solution I'm going to re-implement everything in C++, which I prefer to avoid for my current project.
I've asked the question on #haskell but I didn't get a response, maybe it was not the good time of the day to ask.
The simplest implementation I could think of: just wrap STUArray
/IOUArray
operations with fromEnum
/toEnum
.
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module UnpackedEnumArray (STUEArray, IOUEArray) where
import Control.Monad.ST
import Data.Array.Base
import Data.Array.IO
import Data.Array.ST
data STUEArray s i e = STUEArray { fromSTUEArray :: STUArray s i Int }
instance (Enum e) => MArray (STUEArray s) e (ST s) where
getBounds = getBounds . fromSTUEArray
getNumElements = getNumElements . fromSTUEArray
newArray is = fmap STUEArray . newArray is . fromEnum
newArray_ = fmap STUEArray . newArray_
unsafeRead (STUEArray a) = fmap toEnum . unsafeRead a
unsafeWrite (STUEArray a) i = unsafeWrite a i . fromEnum
data IOUEArray i e = IOUEArray { fromIOUEArray :: IOUArray i Int }
instance (Enum e) => MArray IOUEArray e IO where
getBounds = getBounds . fromIOUEArray
getNumElements = getNumElements . fromIOUEArray
newArray is = fmap IOUEArray . newArray is . fromEnum
newArray_ = fmap IOUEArray . newArray_
unsafeRead (IOUEArray a) = fmap toEnum . unsafeRead a
unsafeWrite (IOUEArray a) i = unsafeWrite a i . fromEnum
Now you can
import UnpackedEnumArray
main = do
a <- newArray (0,9) Constructor0 :: IO (IOUEArray Int MyType)
getAssocs a >>= print
Likewise, IArray
instances could be trivially written as well.
Making an instance for MArray IOUarray MyType IO
should be possible. Take a look at the source for the instance declaration for MArray IOUarray Bool IO
.
Since Bool is an instance of both Enum
and Bounded
(and not much else) they probably use functions from those classes when making the instance.
You might have to derive Bounded
but that is probably not an issue since unboxed arrays can contain fixed size elements only.
Edit:
In this article one can read
You can even implement unboxed arrays yourself for other simple types, including enumerations.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With