-- FloatExpansion.hs
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DataKinds #-}
module FloatExpansion where
import Foreign
import Data.Vector.SEXP
import Foreign.R (SEXP)
import qualified Foreign.R.Type as R
import Numeric
import Data.Int
foreign export ccall floatExpand :: Ptr Int -> Ptr Double -> Ptr (SEXP s R.Int) -> IO ()
floatExpand :: Ptr Int -> Ptr Double -> Ptr (SEXP s R.Int) -> IO ()
floatExpand base x result = do
base <- peek base
x <- peek x
let expansion = floatToDigits (toInteger base) x
let sequence = Prelude.map intToInt32 (Prelude.replicate (- snd expansion) 0 Prelude.++ fst expansion)
poke result $ toSEXP $ Data.Vector.SEXP.fromList sequence
intToInt32 :: Int -> Int32
intToInt32 i = fromIntegral (i :: Int) :: Int32
dyn.load("FloatExpansion.so")
.C("HsStart")
floatExpand <- function(x, base=2L){
.C("floatExpand", base=as.integer(base), x=as.double(x), result=list(integer(1)))$result[[1]]
}
> floatExpand(runif(1)) [1] 0 1 0 1 1 1 1 1 0 0 0 1 1 1 1 1 1 1 0 1 1 1 1 0 0 0 0 0 1 1 1 > floatExpand(runif(1)) [1] 1 0 0 0 1 1 1 0 0 0 0 0 1 0 1 1 1 0 0 0 0 0 1 1 1 1 0 1 1 0 1 1 > floatExpand(runif(1)) [1] 1 0 0 0 0 0 0 1 0 1 1 1 1 0 1 1 0 1 1 0 1 0 0 0 1 0 0 0 1 0 1 1 > floatExpand(runif(1)) [1] -729759156 -1459518312
--
You received this message because you are subscribed to the Google Groups "haskellr" group.
To unsubscribe from this group and stop receiving emails from it, send an email to haskellr+unsubscribe@googlegroups.com.
To post to this group, send email to hask...@googlegroups.com.
To view this discussion on the web, visit https://groups.google.com/d/msgid/haskellr/51e55525-52fc-428e-896c-08fe47d17882%40googlegroups.com.
I've just figured out that there's no need of Foreign.R to output a vector... Simply use pokeArray instead of poke !
--
You received this message because you are subscribed to the Google Groups "haskellr" group.
To unsubscribe from this group and stop receiving emails from it, send an email to haskellr+unsubscribe@googlegroups.com.
To post to this group, send email to hask...@googlegroups.com.
To view this discussion on the web, visit https://groups.google.com/d/msgid/haskellr/930fee6c-7737-47e0-88d5-0a81c8c1619b%40googlegroups.com.
Note that R arrays are not represented exactly the same as plain C arrays. So plain pokeArray won't quite work. There is an R specific header at the front of the array, of indeterminate size. Given a pointer to an R array, if you want to index the array for a write or for a read, you'll need to skip the header first. Data.Vector.SEXP does that under the hood. Furthermore, the array needs to be allocated in the R heap, using R's allocation functions. That module also takes care of that.
On 12 August 2016 at 15:39, 'Stéphane Laurent' via haskellr <hask...@googlegroups.com> wrote:
Hmmm not really: this requires to know in advance the length of the vector.
Le vendredi 12 août 2016 14:18:51 UTC+2, Stéphane Laurent a écrit :I've just figured out that there's no need of Foreign.R to output a vector... Simply use pokeArray instead of poke !
Le jeudi 11 août 2016 14:53:59 UTC+2, Stéphane Laurent a écrit :It works perfectly. I've written all this on my blog: http://stla.github.io/stlapblog/posts/FloatExpansionHaskell.htmlI am still a newbie in Haskell, don't hesitate to send me your comments.
--
You received this message because you are subscribed to the Google Groups "haskellr" group.
To unsubscribe from this group and stop receiving emails from it, send an email to haskellr+u...@googlegroups.com.
To post to this group, send email to hask...@googlegroups.com.
To unsubscribe from this group and stop receiving emails from it, send an email to haskellr+unsubscribe@googlegroups.com.
To post to this group, send email to hask...@googlegroups.com.
To view this discussion on the web, visit https://groups.google.com/d/msgid/haskellr/6a2d00c7-bc56-4e19-bb40-174ce109d224%40googlegroups.com.