create a dll returning a R list

48 views
Skip to first unread message

Stéphane Laurent

unread,
Aug 10, 2016, 4:42:12 AM8/10/16
to haskellr
Hello, 
After compiling the module below by this way, the call in R returns the list: 
[[1]]
[1] 1 2 3

I have not managed to return a list with two elements. Is it possible ?


The module:
-- Test.hs
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DataKinds #-}

module Test where

import Foreign
import Data.Vector.SEXP
import Foreign.(SEXP)
import qualified Foreign.R.Type as R

foreign 
export ccall testR :: Ptr (SEXP s R.Real) -> IO ()

testR 
:: Ptr (SEXP s R.Real) -> IO ()
testR result 
= do
  let ds 
= toSEXP $ Data.Vector.SEXP.fromList ([1, 2, 3] :: [Double])
  poke result $ ds

Stéphane Laurent

unread,
Aug 12, 2016, 8:32:34 AM8/12/16
to haskellr
I've found a solution... I will post it within a couple of days.

Stéphane Laurent

unread,
Aug 14, 2016, 12:14:03 PM8/14/16
to haskellr
Here is an example. The floorfrac function takes a list of numbers and returns a pair of two lists. The first list of the pair has type [Int] and the second one has type [Double].
To make the function compatible with R, returning a list of two vectors, these two vectors must have the same type. Hence I use fromIntegral to convert the [Int] list.

-- FloorFracR.hs
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DataKinds #-}

module FloorFracR where
import Foreign
import Foreign.C
import Foreign.R (SEXP)
import qualified Foreign.R.Type as R
import qualified Data.Vector.SEXP as DV

floorfrac
:: [Double] -> ([Int], [Double])
floorfrac xs
= (integerParts, fractionalParts)
           
where integerParts = map floor xs
                  fractionalParts
= zipWith (-) xs (map fromIntegral integerParts)

foreign
export ccall floorfracR :: Ptr CDouble -> Ptr CInt -> Ptr (SEXP s R.Real) -> IO()
floorfracR
:: Ptr CDouble -> Ptr CInt -> Ptr (SEXP s R.Real) -> IO()
floorfracR xs n result
= do
  n
<- peek n
  xs
<- peekArray (fromIntegral n :: Int) xs
  let
(integerParts, fractionalParts) = floorfrac $ map realToFrac xs
  pokeArray result $ map
(DV.toSEXP . DV.fromList) [map fromIntegral integerParts, fractionalParts]

In summary:
- create two lists of numbers of the same type, create a list containing these two lists
- map DV.toSEXP . DV.fromList to this list
- use pokeArray

To invoke the function in R, once you get the compiled library:

> dyn.load("FloorFrac.so")
> .C("HsStart")
list()
> input <- c(1.5, 2.6)
> .C("floorfracR", xs=as.double(input), n=length(input), result=list(0,0))$result
[[1]]
[1] 1 2

[[2]]
[1] 0.5 0.6

Note that the result argument must be given as a list whose length is the number of vectors of the output.

Stéphane Laurent

unread,
Sep 10, 2017, 6:59:56 AM9/10/17
to haskellr
Here is a way to return a list of vectors with arbitrary length, without knowing in advance the length: https://laustep.github.io/stlahblog/posts/YoungTableaux.html
Reply all
Reply to author
Forward
0 new messages