Marshalling lists of lists

26 views
Skip to first unread message

Stéphane Thibaud

unread,
Feb 13, 2017, 3:35:13 AM2/13/17
to haskellr
I have the following two lines of code that I would like to test, but from the documentation, I do not immediately see how to convert this datatype. I think it should be represented by a list of vectors in R.
The following code does not work, since a list of lists is not defined in Language.R.Literal:

let predictors = [[3.4 :: Double, 5.7 :: Double], [5.4 :: Double, 8.7 :: Double]]
H.printQuote [r|predictors_hs|]


A quick tip?


Best regards,

Stéphane

Alexander Vershilov

unread,
Feb 14, 2017, 2:07:53 PM2/14/17
to haskellr
Hello,  Stéphane.

Sorry that tip will be a bit long, the required functionality is missing in the inline-r
itself, and functionality that will make it easy is being prepared. It's likely to be
merged in following weeks.

However it's possible to do it on the user level. I'm providing a standalone executable
that shows how to do that, if you work in ghci, you'll need to compile that file and
load it in your session:

{-# LANGUAGE GADTs #-}   -- in order to use HEXP
{-# LANGUAGE ForeignFunctionInterface #-} -- in order to add missing function
{-# LANGUAGE MultiParamTypeClasses #-}  -- in order to write Literal instance
{-# LANGUAGE DataKinds #-}  -- in order to use sexp subtypes
{-# LANGUAGE ViewPatterns #-} -- in order to use HEXP
{-# LANGUAGE QuasiQuotes #-} -- in order to use [r| quasi quote


module Main where




import Language.R.Instance as R
import Language.R.Literal as R
import Language.R.QQ
import H.Prelude as H
import Data.Int


import Foreign.C
import Foreign.R.Type as R
import qualified Data.Vector.SEXP as SVector
import qualified Foreign.R as R
import Foreign.R.Internal (SEXP0)


import System.IO.Unsafe

-- We can introduce new type with required behavior
newtype
Matrix = Matrix [[Double]] deriving (Eq,Show)

-- This is function that allow us to write new attribute to SEXP, it's missing in latest inline-r
foreign import ccall safe "Rinternals.h Rf_setAttrib" cRfSetAttrib :: SEXP0 -> SEXP0 -> SEXP0 -> IO ()


-- User friendly wrapper
rfSetAttrib :: SEXP s a -> SEXP s2 b -> SEXP s3 c -> IO ()
rfSetAttrib a b c = cRfSetAttrib (R.unsexp a) (R.unsexp b) (R.unsexp c)


-- Instance for matrix, looks scarry as it works in IO, and can
-- use automatic protection used in R.
instance Literal Matrix '
R.Real where
  mkSEXPIO
(Matrix xs) =
    let n
= fromIntegral $ length xs :: Int32
        m
= fromIntegral $ length (head xs) :: Int32
   
in R.withProtected (mkSEXPIO $ concat xs) $ \s ->
        R
.withProtected (withCString "dim" R.install) $ \dim_name ->
           R
.withProtected (mkSEXPIO [n,m]) $ \dims -> do
               rfSetAttrib s dim_name dims
               
return s
  fromSEXP s@
(hexp -> H.Real v) =
   
case R.getAttribute s (unsafePerformIO $ withCString "dim" R.install) of
     
(hexp -> H.Int k) ->
        let l
= SVector.toList v
           
[_,n] = SVector.toList k
       
in Matrix $ chunk n l
      _
-> error "not a matrix"
  fromSEXP _
= error "Wrong type"


-- Helper (can be taked from split package)
chunk
:: Int32 -> [a] -> [[a]]
chunk _
[] = []
chunk n xs
= let (h,t) = splitAt (fromIntegral n) xs
             
in h : chunk n t


-- Test:


main
:: IO ()
main
= do
    R
.withEmbeddedR R.defaultConfig $
      R
.runRegion $ do
        let predictors
= Matrix [[3.4 :: Double, 5.7 :: Double, 6], [5.4 :: Double, 8.7 :: Double, 9]]
        x
<- [r|predictors_hs|]
        R
.unSomeSEXP x (io . R.printValue)
        let k
= fromSEXP (R.cast R.SReal x) :: Matrix
        io $
print (k,  k == predictors)





Output its:
sh-4.4$ ./marshal
     
[,1] [,2] [,3]
[1,]  3.4  6.0  8.7
[2,]  5.7  5.4  9.0
(Matrix [[3.4,5.7,6.0],[5.4,8.7,9.0]],True)

I hope it helps. We will keep you updated when more user friendly solution will land in inline-r.

--
Alexander Vershilov,
Software engineer at Tweag I/O
Reply all
Reply to author
Forward
0 new messages