bug dll

19 views
Skip to first unread message

Stéphane Laurent

unread,
Aug 10, 2016, 7:23:08 AM8/10/16
to haskellr
Hello, 
 I've created a dll that I call in R. It should always return a sequence of 0 and 1. However it bugs : sometimes it returns other integers, sometimes it causes a crash in R.

The module:
-- 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

The auxiliary StartEnd.c file:
// StartEnd.c
#include <Rts.h>

void HsStart()
{
int argc = 1;
char* argv[] = {"ghcDll", NULL}; // argv must end with NULL

// Initialize Haskell runtime
char** args = argv;
hs_init(&argc, &args);
}

void HsEnd()
{
hs_exit();
}

The compilation:
ghc -package-db /home/stla/.cabal-sandbox/x86_64-linux-ghc-7.10.3-packages.conf.d -c FloatExpansion.hs
ghc -package-db /home/stla/.cabal-sandbox/x86_64-linux-ghc-7.10.3-packages.conf.d -shared -fPIC -dynamic -lHSrts-ghc7.10.3 FloatExpansion.hs StartEnd.c -o FloatExpansion.so

The call in R:
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]]  
}

The floatExpand function takes a number x between 0 and 1 and returns its binary expansion.
Examples (a bug at the fourth example):
> 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

The bug is non-deterministic : it occurs that floatExpand(x) bugs a first time but returns the correct result the second time (with the same x).

Stéphane Laurent

unread,
Aug 10, 2016, 7:50:22 AM8/10/16
to haskellr
In fact, the problem has nothing to do with Foreign.R.
Indeed, I have written the same module which returns the output in a CString instead of a SEXP. And it bugs too.

Stéphane Laurent

unread,
Aug 11, 2016, 5:12:22 AM8/11/16
to haskellr
I found the problem:
Ptr Int -> Ptr Double
Correction:
Ptr CInt -> Ptr CDouble

No bug anymore :)

Boespflug, Mathieu

unread,
Aug 11, 2016, 5:32:03 AM8/11/16
to Stéphane Laurent, haskellr
Glad you found the solution! Indeed, using the C* types is a common snag when dealing with the Haskell FFI. It's very cool that you managed to get HaskellR working the other way round: by having R call Haskell rather that Haskell calling R! We knew this was possible to do but hadn't tried yet.

As soon as you have a small prototype going, would be glad a to see a PR adding it as an example in the examples folder. :)

--
Mathieu Boespflug
Founder at http://tweag.io.

--
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.

For more options, visit https://groups.google.com/d/optout.

Stéphane Laurent

unread,
Aug 11, 2016, 8:53:59 AM8/11/16
to haskellr
It works perfectly. I've written all this on my blog: http://stla.github.io/stlapblog/posts/FloatExpansionHaskell.html
I am still a newbie in Haskell, don't hesitate to send me your comments. 

Stéphane Laurent

unread,
Aug 12, 2016, 8:18:51 AM8/12/16
to haskellr

I've just figured out that there's no need of Foreign.R to output a vector... Simply use pokeArray instead of poke !

Stéphane Laurent

unread,
Aug 12, 2016, 9:39:56 AM8/12/16
to haskellr
Hmmm not really: this requires to know in advance the length of the vector.

Boespflug, Mathieu

unread,
Aug 12, 2016, 12:39:12 PM8/12/16
to Stéphane Laurent, haskellr
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.

--
Mathieu Boespflug
Founder at http://tweag.io.

--
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.

Stéphane Laurent

unread,
Aug 13, 2016, 5:32:48 AM8/13/16
to haskellr
Thank you for these notes. 
Do you know what is the meaning of "s" in (SEXP s R.Int) ?


Le vendredi 12 août 2016 18:39:12 UTC+2, Mathieu Boespflug a écrit :
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.

--
Mathieu Boespflug
Founder at http://tweag.io.

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.html
I 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.

Boespflug, Mathieu

unread,
Aug 13, 2016, 7:38:03 AM8/13/16
to Stéphane Laurent, haskellr
You can think of that "s" as a tag, marking the memory region to which the value belongs. Memory regions are useful because HaskellR effectively switches off R's garbage collector for any SEXP value that it creates. We have to do this because R can't possibly be aware of whether a given R value is alive or dead, since there might still be a reference to it from somewhere in the Haskell heap, which R doesn't know about. Since there is no garbage collection for a SEXP, creating a value inside a region makes it possible to nonetheless deallocate a value safely once nothing is referring to it anymore. The invariant is: so long as some given region is in scope, no value allocated in it can be deallocated. But as soon as control flow of the program exits the scope of the region, nothing can point to anything in the region, making it safe to deallocate *all* values tagged with that region shortly thereafter.

Tagging values at the type level makes trying to violate this invariant a type error at compile time.

Currently HaskellR only supports one region, called the global region. But there is experimental work under way to support multiple nested regions too.

For most small programs, you can essentially ignore this type parameter, and not bother with multiple regions. For more information, see the HaskellR documentation: http://tweag.github.io/HaskellR/docs/managing-memory.html.

--
Mathieu Boespflug
Founder at http://tweag.io.

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.
Reply all
Reply to author
Forward
0 new messages