Rlang-QQ-0.1.1.0: quasiquoter for inline-R code

Safe HaskellNone

RlangQQ

Contents

Description

A quasiquoter to help with calling R from ghc.

Synopsis

the quasiquoter

r :: QuasiQuoterSource

Calls R with the supplied string. Variables in R prefixed hs_ cause the corresponding (un-prefixed) variable to be converted. The variable(s) must be in at least one class FromRDS or ToRDS. Currently the relation between where variables are used and assigned to (using <-) determines the Intent.

Expressions are also supported. These must be text between $( ), just like template haskell. One condition is that the contents between the parentheses must be parseable by haskell-src-meta/haskell-src-exts. So if you find the hs_ notation unpleasant you can still interpolate using $(x).

An example of both styles is

 
 import RlangQQ

 x = [0 .. 10  :: Double]

 main = do
   [r|
     library(ggplot2)
     png(file='test.png')
     plot(qplot( hs_x, $(map (sin . (*pi) . (/10)) x) ))
     dev.off()
     |]

You get a plot:

While it is only somewhat usable, you can have Rnw/Rmd documents (knitr) that include haskell code. One example is given here

rChan :: QuasiQuoterSource

same as [rChan| |] does the same as [r| |], except the return value will be a Chan (Record a).

conversion of values

class ToRDS a Source

same as Binary but should be compatible with R's saveRDS binary mode, which is for single objects

Instances

ToRDS Double 
ToRDS Int32 
ToRDS String

abc => c('ab')

ToRDS Text

T.pack abc => c('ab')

ToRDS [Double] 
ToRDS [Int32] 
ToRDS [String]

["abc","def"] => c('abc','def')

ToRDSRecord k __ ___ xs => ToRDS (Record xs)

lab .=. val .*. emptyRecord => list(lab= (toRDS val) ).

The type variables with underscores should be hidden

ToRDS (Vector Double)

becomes a numeric vector

ToRDS (Vector Int32)

integer vector

ToRDS (Vector Text)

character vector c('ab','cd')

(ToRDS t, ToRDS (RDA rs), ShowLabel k l2) => ToRDS (RDA (: * (LVPair k l2 t) rs))

internal

ToRDS (RDA ([] *))

internal

IxSize i => ToRDS (Array i Int32) 
IxSize i => ToRDS (Array i Double)

Data.Array.Array become arrays in R

(ToRDS t, ShowLabel k l) => ToRDS (LVPair k l t)

probably internal

(Source r Int32, Shape sh) => ToRDS (Array r sh Int32)

repa

(Source r Double, Shape sh) => ToRDS (Array r sh Double)

repa

class FromRDS a Source

Instances

FromRDS Double 
FromRDS Int32 
FromRDS String 
FromRDS Text 
FromRDS [Double] 
FromRDS [Int32] 
FromRDS [String] 
FromRDSRec a b as' as'2 bs' => FromRDS (Record bs') 
FromRDS (Vector Double) 
FromRDS (Vector Int32) 
FromRDS (Vector Text) 
(FromRDS t, FromRDS (RDA rs), ShowLabel k l2) => FromRDS (RDA (: * (LVPair k l2 t) rs))

internal

FromRDS (RDA ([] *))

internal

IxSize i => FromRDS (Array i Int32)

note indices become 0-based (see IxSize)

IxSize i => FromRDS (Array i Double)

note indices become 0-based (see IxSize)

(FromRDS t, ShowLabel k l) => FromRDS (LVPair k l t)

probably internal

Shape sh => FromRDS (Array U sh Int32)

repa

Shape sh => FromRDS (Array U sh Double)

repa

records

If the quasiquote assigns to variables hs_x and hs_y, the result type will be IO (Record '[LVPair x x, LVPair y y]). The types x and y have to be determined on the haskell side. Here is a complete example:

>>> :set -XQuasiQuotes -XDataKinds -XNoMonomorphismRestriction
>>> let x = [2 :: Double]
>>> let q = [r| hs_y <- 1 + hs_x; hs_z <- 2 |]

These labels could be generated by template haskell with $(makeLabels6 (words "y z"))

>>> let y = Label :: Label "y"
>>> let z = Label :: Label "z"
>>> do o <- q; print (o .!. y ++ o .!. z :: [Double])
[3.0,2.0]

listToRecN :: ListToRecN __ (n :: HNat) x r => Proxy n -> [x] -> Record rSource

convert a haskell list into a record with labels all of type "". The length of the list is decided by the (type of the) first argument which is a HNat

n :: QuasiQuoterSource

HList uses it's own nat, distinct from Nat, for various reasons.

Specifying those HNat can be done like:

 [n| 5 |]

which is shorter than the equivalent

 hSucc $ hSucc $ hSucc $ hSucc $ hSucc hZero

connecting to a single R session

Variables like ch_x ch_longVariableName inside the quasiquote generate references to x and longVariableName. These variables should have type Chan (a, b -> IO '()'). newChan can produce values of that type, but some versions with restricted types are provided:

 do
  x <- newRChan
  longVariableName <- newRChan' (undefined :: Double)

The whole input to R is re-sent each time whenever a whole set of ch_ variables is available. examples/test4.hs has an a working example shows that keeping the same R-session open is much faster, but that results may be confusing since nothing explicitly says (besides this documentation here) that the same code is re-sent.

newRChan :: IO (Chan (a, b -> IO ()))Source

newChan with a more restricted type

newRChan' :: a -> IO (Chan (a, b -> IO ()))Source

newRChan (undefined :: Double) produces an even more restricted type than newRChan', which can help make type errors more sensible and/or avoid ambiguous type variable

sendRcv :: Chan (t, b -> IO ()) -> t -> IO bSource

y <- sendRcv c x sends the value x using the chan c. Provided that an [r| |] quasiquote above refers to a ch_c, the call to sendRcv will eventually produce a Record y

TODO

debugging
Write file that can be run to loading a quote into R interpreter (ie the same thing as readProcess R --no-save ...). For now it's pretty simple to just cd Rtmp and load/source things. also, return R's stdout stderr exitcode in the HList. This won't be practical for the Chan option since the stdout is getting consumed?
antiquote
doesn't do escapes, so a string '$( blah )' might end badly
more examples
conversion both ways etc.
read NULL as Maybe?
more datatypes
support things like ??, ...
call R functions as if they were defined in haskell
This can be achievede already by doing something like
 x <- newRChan
 [r| hs_f <- ch_x + 1 |]
 let f :: Double -> IO Double
     f xVal = (.!. (Label :: Label "f")) `fmap` sendRcv x xVal

But perhaps something can be done to generate the above code from something much shorter like:

 [r| hs_f <- function(x) x + 1 |]

Can this be made to work without looking at whether there is a function() after the <-?

call hs functions as if they were defined in R
we might like to be able to have values like f x = x + 1 be callable by.
use libR.so
there is a hR package which might allow usage similar to hslua (ie. calling individual R functions)

one drawback is that it uses lists for vectors...

static analysis
(optionally?) call something like codetools on the generated R code to infer result/argument types. Or perhaps translate R code into some constraints:
 class RApp (x :: [*]) r
 instance (UpcastNumR a b ~ r, UpcastNumR b a ~ r) => RApp [Proxy "+", a, b] r
 type family UpcastNumR a b
 type instance UpcastNumR Double Int = Double
 type instance UpcastNumR Int Int = Int

the benefit here is that users could add their own RApp instances. On the other hand, perhaps using a separate constraint solver will be less confusing in terms of type errors (ie. failure to infer a type from R which will happen (features like do.call) should not complicate the types seen on the haskell side).

or run the code first with some dummy inputs (say vectors of length 10 or so), and assume those types will continue to be the same.