寻找 «instance (Enum a, Bounded a) => IArray UArray a»
我正在寻找一种方法来让 Enum a =>; UArray a
(这对我来说很有意义,因为我们可以轻松地将枚举映射到 Int
并通过 toEnum
和 fromEnum
返回)
到目前为止我试图从 UArray Int 的代码href="http://hackage.haskell.org/packages/archive/array/0.3.0.1/doc/html/src/Data-Array-Base.html" rel="nofollow" title="Data.Array.Base ">Data.Array.Base 并到处走私一些 toEnum
和 fromEnum
:
{-# LANGUAGE MagicHash, UnboxedTuples #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module UArrays where
import Data.Array.Base
import Data.Array.ST
import Data.Array.Unboxed
import GHC.Base -- (Int(I#), Int#(..))
import GHC.Prim -- (indexIntArray#, readIntArray#, writeIntArray#)
import GHC.ST (ST(..), runST)
import Unsafe.Coerce
instance (Enum a, Bounded a) => IArray UArray a where
{-# INLINE bounds #-}
bounds (UArray l u _ _) = (l, u)
{-# INLINE numElements #-}
numElements (UArray _ _ n _) = n
{-# INLINE unsafeArray #-}
unsafeArray lu ies = runST (unsafeArrayUArray lu ies minBound)
{-# INLINE unsafeAt #-}
unsafeAt (UArray _ _ _ arr#) (I# i#) =
I# $ fromEnum (indexIntArray# arr# i#)
{-# INLINE unsafeReplace #-}
unsafeReplace arr ies = runST (unsafeReplaceUArray arr ies)
{-# INLINE unsafeAccum #-}
unsafeAccum f arr ies = runST (unsafeAccumUArray f arr ies)
{-# INLINE unsafeAccumArray #-}
unsafeAccumArray f initialValue lu ies =
runST (unsafeAccumArrayUArray f initialValue lu ies)
-- data STUArray s i e = STUArray !i !i !Int (GHC.Prim.MutableByteArray# s)
instance (Enum a, Bounded a) => MArray (STUArray s) a (ST s) where
{-# INLINE getBounds #-}
getBounds (STUArray l u _ _) = return (l, u)
{-# INLINE getNumElements #-}
getNumElements (STUArray _ _ n _) = return n
{-# INLINE unsafeNewArray_ #-}
unsafeNewArray_ (l, u) = unsafeNewArraySTUArray_ (l, u) wORD_SCALE
{-# INLINE newArray_ #-}
newArray_ arrBounds = newArray arrBounds minBound
{-# INLINE unsafeRead #-}
-- unsafeRead :: GHC.Arr.Ix i => a i e -> Int -> m e
unsafeRead (STUArray _ _ _ marr#) (I# i#) =
ST $ \ s1# ->
case readIntArray# marr# i# s1# of
(# s2#, e# #) -> (# s2#, I# (toEnum e#) #)
{-# INLINE unsafeWrite #-}
-- unsafeWrite :: GHC.Arr.Ix i => a i e -> Int -> e -> m ()
unsafeWrite (STUArray _ _ _ marr#) (I# i#) (I# e#) =
ST $ \ s1# ->
case writeIntArray# marr# (unsafeCoerce i#) (I# $ fromEnum e#) s1# of
s2# -> (# s2#, () #)
但是它当然不能编译:
[2 of 4] Compiling UArrays ( UArrays.hs, interpreted )
UArrays.hs:27:14:
Couldn't match expected type `Int#' with actual type `Int'
In the return type of a call of `fromEnum'
In the second argument of `($)', namely
`fromEnum (indexIntArray# arr# i#)'
In the expression: I# $ fromEnum (indexIntArray# arr# i#)
UArrays.hs:52:45:
Couldn't match expected type `Int' with actual type `Int#'
In the first argument of `toEnum', namely `e#'
In the first argument of `I#', namely `(toEnum e#)'
In the expression: I# (toEnum e#)
UArrays.hs:57:57:
Couldn't match expected type `Int#' with actual type `Int'
In the return type of a call of `fromEnum'
In the second argument of `($)', namely `fromEnum e#'
In the third argument of `writeIntArray#', namely
`(I# $ fromEnum e#)'
Failed, modules loaded: Utils.
还有没有魔法unboxInt :: Int - >
,并且 GHC.*
中的 Int#I#
上的模式匹配不会产生 Int
,而是产生 Int #
相反,但不知何故 UArray Int
存在并且可以在 Int#
上工作。
我还找到了一篇关于 制作用于新类型的 UArray,但它似乎并不适用,因为它依赖于 unsafeCoerce
。我尝试过,但它生成了一个有趣的 listArray (0, 54) $cycle [Red, Yellow, Green]
,其中所有构造函数都是 Blue
。
我是不是走错了路?
更新:
现在可以使用了,这里是源代码:
- UArrays.hs:http://hpaste。 org/56728
- BenchmarkUArray.hs:http://hpaste.org/56729
- Makefile: http://hpaste.org/56727
如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。
绑定邮箱获取回复消息
由于您还没有绑定你的真实邮箱,如果其他用户或者作者回复了您的评论,将不能在第一时间通知您!
发布评论
评论(2)
您需要认识到
Int
是一个装箱整数,它是通过构造函数I#
从未装箱整数Int#
构造的。因此:由于
fromEnum
已经返回一个装箱整数,因此您不必通过再次应用I#
来重新装箱它,因此在此代码片段中,例如:。 ..您可以简单地省略
I#
构造函数。同样,当使用 toEnum 时,您应该应用 I# 构造函数从未装箱的整数中获取装箱的整数。正如 @leftaroundabout 提到的,与使用简单的方法相比,除了
fromEnum
和toEnum
可能具有的复杂性(特别是对于元组等)之外,这种装箱和拆箱可能会导致性能降低装箱数组。You need to realize that
Int
is a boxed integer that is constructed from an unboxed integerInt#
via the constructorI#
. So:Since
fromEnum
already returns a boxed integer, you don't have to re-box it by applyingI#
again, so in this code snippet, for instance:... you can simply leave out the
I#
constructor. Similarly, when usingtoEnum
, you should apply theI#
constructor to get a boxed integer out of an unboxed integer.As @leftaroundabout mentioned, this boxing and unboxing in addition to the complexity that
fromEnum
andtoEnum
can have (Especially for tuples, etc) might lead to less performance compared to using simple boxedArray
s.警告:函数
fromEnum 。 toEnum
并不总是双射,因此这不适用于所有枚举类型。特别是,Double
是一个Enum
实例,但toEnum
只是截断Double
值。这样做的原因是,如果您想编写像
[0, 0.1 .. 1]
这样的表达式,则必须实现Enum
类型类。但一般来说,您所做的对于某些类型来说显然不起作用。Warning: The function
fromEnum . toEnum
is not always a bijection, so this will not work for all enum types. In particular,Double
is anEnum
instance, buttoEnum
just truncatesDouble
values.The reason for this is because
Enum
is the type class you must implement if you want to write expressions like[0, 0.1 .. 1]
. But generally speaking, what you're doing will just plain not work for some types.