我正在尝试将整数矩阵实现为swapLines
。它应该给我一个快速Vector (Unboxed.Vector Int)
操作,它只在内存中写入一个本机指针,而不是复制几个整数。它应该比crashBigMatrix
具有更少的内存间接,因为所有类型都是未提升的。
对于小矩阵,它工作正常,但是当我增加大小时会出现段错误。尝试运行{-# LANGUAGE MagicHash, UnboxedTuples #-}
module Matrix where
import Control.Monad.ST
import GHC.ST
import GHC.Exts
import GHC.Prim
import GHC.Magic(runRW#)
data Matrix = Matrix ArrayArray# -- lifts the array from # to *
data MutableMatrix s = MutableMatrix (MutableArrayArray# s)
generateLine :: MutableByteArray# s -> Int# -> Int# -> Int# -> (Int -> Int -> Int) -> State# s -> State# s
generateLine mbar curLine curCol colCount genFunc s =
case curCol ==# colCount of
0# -> case genFunc (I# curLine) (I# curCol) of
(I# x) -> generateLine mbar curLine (curCol +# 1#) colCount genFunc (writeIntArray# mbar curCol x s) -- if curCol is replaced by 0#, doesn't crash
_ -> s
initLines :: MutableArrayArray# s -> Int# -> Int# -> Int# -> (Int -> Int -> Int) -> State# s -> State# s
initLines mat curLine lineCount colCount genFunc s =
case curLine ==# lineCount of
1# -> s
0# -> case newByteArray# (4# *# colCount) s of -- TODO sizeof Int ?
(# s1, mbar #) -> case unsafeFreezeByteArray# mbar (generateLine mbar curLine 0# colCount genFunc s1) of
(# s2, bar #) -> initLines mat (curLine +# 1#) lineCount colCount genFunc
(writeByteArrayArray# mat curLine bar s2) -- only writes a pointer to the ByteArray
generateMutable# :: Int# -> Int# -> (Int -> Int -> Int) -> State# s -> (# State# s, MutableArrayArray# s #)
generateMutable# lineCount colCount genFunc s =
case newArrayArray# lineCount s of
(# s1, marrarr #) -> (# initLines marrarr 0# lineCount colCount genFunc s1 , marrarr #)
crashBigMatrix :: Int
crashBigMatrix =
case (runRW# $ \s -> case generateMutable# 150000# 4# (\x y -> x) s of
(# s1, marrarr #) -> (# s1, marrarr #)) of
(# _, m #) -> (MutableMatrix m) `seq` 2
,
some text
答案 0 :(得分:4)
如果您执行TODO sizeof Int
:
{-# language CPP #-}
-- imports
#include "MachDeps.h"
然后在代码中:
case newByteArray# (SIZEOF_HSINT# *# colCount) s of
您可以找到MachDeps.h
here的内容。