将 Haskell 中数组的指针传递给 C 函数
我有以下 C 代码:
#include <sys/times.h>
#include <time.h>
float etime_( float *tarray )
{ struct tms buf;
times( &buf );
tarray[0] = 1.0 * buf.tms_utime / CLOCKS_PER_SEC;
tarray[1] = 1.0 * buf.tms_stime / CLOCKS_PER_SEC;
return tarray[0] + tarray[1];
}
尝试将此 Fortran 代码移植到 Haskell:
PROGRAM Test
IMPLICIT NONE
REAL t, ta(2), etime
INTEGER i
DOUBLE PRECISION x
do i = 1, 10000
x = sin( cos( i * 1.0 d0 ) )
print *, x
enddo
ta(1) = 0.0d0
ta(2) = 0.0d0
t = etime( ta )
PRINT *, 'user time: ', ta(1)
PRINT *, 'system time: ', ta(2)
PRINT *, 'process time: ', t
END
如何定义数组和! 或者 !!! 为了让下面的代码工作?
module Main where
import GHC.Ptr
import GHC.Prim
import System.IO.Unsafe
import Control.Monad
foreign import ccall etime_ :: Ptr Double → IO Double
etime = etime_
main :: IO Int
main = do
mapM_ (print . sin . cos . (* (1.0 :: Double)) . fromIntegral) [1..10000 :: Int]
ta ← array 2
t ← etime ta
putStrLn $ "user time: " ++ show (ta !!! 0)
putStrLn $ "system time: " ++ show (ta !!! 1)
putStrLn $ "process time: " ++ show t
return 0
array :: Int → IO (Ptr a)
array size = undefined
(!) :: Ptr a → Int → IO a
(!) = undefined
(!!!) :: Ptr a → Int → a
(!!!) = undefined
I have the following C code:
#include <sys/times.h>
#include <time.h>
float etime_( float *tarray )
{ struct tms buf;
times( &buf );
tarray[0] = 1.0 * buf.tms_utime / CLOCKS_PER_SEC;
tarray[1] = 1.0 * buf.tms_stime / CLOCKS_PER_SEC;
return tarray[0] + tarray[1];
}
Trying to port this Fortran code to Haskell:
PROGRAM Test
IMPLICIT NONE
REAL t, ta(2), etime
INTEGER i
DOUBLE PRECISION x
do i = 1, 10000
x = sin( cos( i * 1.0 d0 ) )
print *, x
enddo
ta(1) = 0.0d0
ta(2) = 0.0d0
t = etime( ta )
PRINT *, 'user time: ', ta(1)
PRINT *, 'system time: ', ta(2)
PRINT *, 'process time: ', t
END
How can I define array and ! or !!! for the below code to work?
module Main where
import GHC.Ptr
import GHC.Prim
import System.IO.Unsafe
import Control.Monad
foreign import ccall etime_ :: Ptr Double → IO Double
etime = etime_
main :: IO Int
main = do
mapM_ (print . sin . cos . (* (1.0 :: Double)) . fromIntegral) [1..10000 :: Int]
ta ← array 2
t ← etime ta
putStrLn $ "user time: " ++ show (ta !!! 0)
putStrLn $ "system time: " ++ show (ta !!! 1)
putStrLn $ "process time: " ++ show t
return 0
array :: Int → IO (Ptr a)
array size = undefined
(!) :: Ptr a → Int → IO a
(!) = undefined
(!!!) :: Ptr a → Int → a
(!!!) = undefined
如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。
绑定邮箱获取回复消息
由于您还没有绑定你的真实邮箱,如果其他用户或者作者回复了您的评论,将不能在第一时间通知您!
发布评论
评论(3)
我建议这样:
但是回答你的具体问题:
我建议使用hoogle来找到你需要的功能。
I suggest this:
but to answer your specific questions:
I suggest to use hoogle to find the functions you need.
以元组形式返回总和、用户时间和系统时间。 请注意,etime 采用的是 float 指针,而不是 double 指针,因此请确保您的类型一致:
Return the sum, user time, and system time as a tuple. Note that etime takes a pointer to float, not double, so make your types agree:
给定以下附加 Haskell 模块:
现在我们可以将这段 Fortran 代码
逐字移植到 Haskell:
Given the following additional Haskell module:
And now we can port this piece of Fortran code:
word for word to Haskell: