| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
RlangQQ.Binary
Description
Conversions between R's RDS/RDA format and haskell data types.
tested with R 3.0.1
Missing:
- Data.Map
- better error reporting when the format is bad?
- more tests
- toRDA :: (ToRDS (RDA (RecordValuesR r)), RecordValues r) => Record r -> ByteString
- fromRDA :: FromRDA r => ByteString -> Record r
- class ToRDS a where
- class FromRDS a where
- type FromRDA r = (Unlabeled' r, FromRDS (RDA (RecordValuesR r)))
- type ToRDSRecord __ ___ xs = (RDSHLIST __ ___, ToRDS (LST ___), RecordValues xs, HList ___ ~ (HList (RecordValuesR xs) `HAppendR` HList `[ListStart, Tagged "names" [String]]`), RecordLabelsString (LabelsOf xs), HAppend (HList (RecordValuesR xs)) (HList `[ListStart, Tagged "names" [String]]`))
- type RDSHLIST xs' xs = (HNat2Integral (HLength xs), HFoldr (HSeq FToRDS) Put xs Put)
- data RDA a
- class Ix i => IxSize i where
- ixSize :: (i, i) -> [Int32]
- fromIxSize :: [Int32] -> (i, i)
- module Data.HList.CommonMain
functions to serialize many variables
A typical type would be
Record '[Tagged l1 (Tagged m1 x), Tagged l2 (Tagged m2 x)]
The outer labels (l1, l2) are those used on the haskell-side. The inner labels
are the m1 m2 which are the names of the variables on the R side.
toRDA :: (ToRDS (RDA (RecordValuesR r)), RecordValues r) => Record r -> ByteString Source
fromRDA :: FromRDA r => ByteString -> Record r Source
serializing a single variable
same as Binary but should be compatible with R's saveRDS
binary mode, which is for single objects
Instances
| ToRDS Double | |
| ToRDS Int | |
| ToRDS Int32 | |
| ToRDS Integer | |
| ToRDS String | "abc" => |
| ToRDS Text | T.pack "abc" => |
| ToRDS [Double] | |
| ToRDS [Int] | converts to an |
| ToRDS [Int32] | |
| ToRDS [Integer] | converts to an |
| ToRDS [String] |
|
| ToRDSRecord k __ ___ xs => ToRDS (Record xs) |
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 |
| ToRDS (Vector Double) | becomes a numeric vector |
| ToRDS (Vector Int32) | |
| (ToRDS t, ToRDS (RDA rs), ShowLabel k l2) => ToRDS (RDA ((:) * (Tagged k l2 t) rs)) | internal |
| ToRDS (RDA ([] *)) | internal |
| IxSize i => ToRDS (Array i Int32) | |
| IxSize i => ToRDS (Array i Double) |
|
| (ToRDS t, ShowLabel k l) => ToRDS (Tagged 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 |
Instances
| FromRDS Double | |
| FromRDS Int | |
| FromRDS Int32 | |
| FromRDS Integer | |
| FromRDS String | |
| FromRDS Text | |
| FromRDS [Double] | |
| FromRDS [Int] | |
| FromRDS [Int32] | |
| FromRDS [Integer] | |
| FromRDS [String] | |
| FromRDSRec b d => FromRDS (Record d) | R lists become HList records. let x = Label :: Label "x"
y = Label :: Label "y"
in x .=. 1
.*. y .=. "b"
.*. emptyRecordYou have to get the result type right
(ie. |
| FromRDS (Vector Double) | |
| FromRDS (Vector Int32) | |
| FromRDS (Vector Text) | |
| FromRDS (Vector Double) | |
| FromRDS (Vector Int32) | |
| (FromRDS t, FromRDS (RDA rs), ShowLabel k l2) => FromRDS (RDA ((:) * (Tagged k l2 t) rs)) | internal |
| FromRDS (RDA ([] *)) | internal |
| IxSize i => FromRDS (Array i Int32) | note indices become 0-based (see |
| IxSize i => FromRDS (Array i Double) | note indices become 0-based (see |
| (FromRDS t, ShowLabel k l) => FromRDS (Tagged k l t) | probably internal |
| Shape sh => FromRDS (Array U sh Int32) | repa |
| Shape sh => FromRDS (Array U sh Double) | repa |
types / internal
type FromRDA r = (Unlabeled' r, FromRDS (RDA (RecordValuesR r))) Source
type ToRDSRecord __ ___ xs = (RDSHLIST __ ___, ToRDS (LST ___), RecordValues xs, HList ___ ~ (HList (RecordValuesR xs) `HAppendR` HList `[ListStart, Tagged "names" [String]]`), RecordLabelsString (LabelsOf xs), HAppend (HList (RecordValuesR xs)) (HList `[ListStart, Tagged "names" [String]]`)) Source
labels are stored with the variables here. compare with the instance for Record / LST which collects
the labels and saves them as an attribute called "names"
Instances
| Wrapped (RDA a) | |
| (FromRDS t, FromRDS (RDA rs), ShowLabel k l2) => FromRDS (RDA ((:) * (Tagged k l2 t) rs)) | internal |
| FromRDS (RDA ([] *)) | internal |
| (ToRDS t, ToRDS (RDA rs), ShowLabel k l2) => ToRDS (RDA ((:) * (Tagged k l2 t) rs)) | internal |
| ToRDS (RDA ([] *)) | internal |
| (~) * (RDA a1) t0 => Rewrapped (RDA a) t | |
| type Unwrapped (RDA a0) = HList a0 |
class Ix i => IxSize i where Source
given bounds of an array, produce a list of how many elements
are in each dimension. For example, a 3x2 array produces [3,2].
A single instance for "linear" indices would look like:
instance (A.Ix i, Num i) => IxSize i where
ixSize x = [fromIntegral (A.rangeSize x)]
fromIxSize [n] = (0, n-1)But to avoid overlapping instances all monomorphic index types likely
to be used are just repeated here. fromIxSize produces 0-based indexes
for instances of Num (Word, Int, Integer), while minBound is
used for other types.
R supports a dimnames attribute. This could be used but it is not so far.
Instances
| IxSize Bool | |
| IxSize Char | |
| IxSize Int | |
| IxSize Int8 | |
| IxSize Int16 | |
| IxSize Int32 | |
| IxSize Int64 | |
| IxSize Integer | |
| IxSize Ordering | |
| IxSize Word | |
| IxSize Word8 | |
| IxSize Word16 | |
| IxSize Word32 | |
| IxSize Word64 | |
| IxSize () | |
| (IxSize a, IxSize b) => IxSize (a, b) | |
| (IxSize a, IxSize b, IxSize c) => IxSize (a, b, c) | |
| (IxSize a, IxSize b, IxSize c, IxSize d) => IxSize (a, b, c, d) | |
| (IxSize a, IxSize b, IxSize c, IxSize d, IxSize e) => IxSize (a, b, c, d, e) |
module Data.HList.CommonMain