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.
目前我将所有内容存储为Word8,然后使用(包装)fromEnum / toEnum进行转换,但感觉不对。我需要严格和拆箱,因为我在内存中使用大型数据结构(> 1.2Go),我无法懒得加载它。如果我找不到任何解决方案,我将重新实现C ++中的所有内容,我希望避免使用当前项目。
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.
我已经问过关于#haskell的问题,但我没有得到回复,也许这不是一天中的好时机。
2 个解决方案
#1
The simplest implementation I could think of: just wrap STUArray
/IOUArray
operations with fromEnum
/toEnum
.
我能想到的最简单的实现:只需用fromEnum / toEnum包装STUArray / IOUArray操作。
{-# 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.
同样,IArray实例也可以简单地编写。
#2
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
.
为MArray创建一个实例IOUarray MyType IO应该是可能的。看一下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.
由于Bool是Enum和Bounded(并没有太多其他)的实例,因此他们可能在创建实例时使用这些类中的函数。
You might have to derive Bounded
but that is probably not an issue since unboxed arrays can contain fixed size elements only.
您可能必须派生Bounded,但这可能不是问题,因为未装箱的数组只能包含固定大小的元素。
Edit:
In this article one can read
在本文中,人们可以阅读
You can even implement unboxed arrays yourself for other simple types, including enumerations.
您甚至可以自己为其他简单类型(包括枚举)实现未装箱的数组。
#1
The simplest implementation I could think of: just wrap STUArray
/IOUArray
operations with fromEnum
/toEnum
.
我能想到的最简单的实现:只需用fromEnum / toEnum包装STUArray / IOUArray操作。
{-# 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.
同样,IArray实例也可以简单地编写。
#2
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
.
为MArray创建一个实例IOUarray MyType IO应该是可能的。看一下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.
由于Bool是Enum和Bounded(并没有太多其他)的实例,因此他们可能在创建实例时使用这些类中的函数。
You might have to derive Bounded
but that is probably not an issue since unboxed arrays can contain fixed size elements only.
您可能必须派生Bounded,但这可能不是问题,因为未装箱的数组只能包含固定大小的元素。
Edit:
In this article one can read
在本文中,人们可以阅读
You can even implement unboxed arrays yourself for other simple types, including enumerations.
您甚至可以自己为其他简单类型(包括枚举)实现未装箱的数组。