[H5r-commits] r21 - / R inst/h5_files man src tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue May 4 23:58:30 CEST 2010


Author: extemporaneousb
Date: 2010-05-04 23:58:29 +0200 (Tue, 04 May 2010)
New Revision: 21

Modified:
   NEWS
   R/h5R.R
   inst/h5_files/ex_1.h5
   inst/h5_files/makeH5.py
   man/H5Obj-class.Rd
   src/h5_wrap.c
   tests/.Rhistory
Log:
Many changes to support the listing of whats in files.




Modified: NEWS
===================================================================
--- NEWS	2010-05-03 18:01:02 UTC (rev 20)
+++ NEWS	2010-05-04 21:58:29 UTC (rev 21)
@@ -8,6 +8,7 @@
                 CHANGES IN h5r VERSION 1.0
 
 NEW FEATURES
+    o Added a way to inspect whats in the h5 file: listH5Contents.
     o Added proper test harness.
     o Added support for hyperslab selection.
     o Added support for string attributes and multi-dim string datasets.

Modified: R/h5R.R
===================================================================
--- R/h5R.R	2010-05-03 18:01:02 UTC (rev 20)
+++ R/h5R.R	2010-05-04 21:58:29 UTC (rev 21)
@@ -270,3 +270,40 @@
 setMethod("length", "H5DataContainer", function(x) if (is.null(dim(x))) x at dims else prod(x at dims))
 setMethod("nrow", "H5DataContainer", function(x) x at dims[1])
 setMethod("ncol", "H5DataContainer", function(x) x at dims[2])
+
+
+##
+## Examining the file contents.
+##
+
+## construct a list of elements in the file.
+.listH5Contents <- function(h5Obj) .Call("h5R_list_contents", .ePtr(h5Obj))
+.listH5Attributes <- function(h5Obj) .Call("h5R_list_attributes", .ePtr(h5Obj))
+
+listH5Contents <- function(h5Obj) {
+  contents <- .listH5Contents(h5Obj)
+  
+  lst <- lapply(contents, function(a) {
+    h5Obj <- switch(as.character(a[[2]]), '0' = { getH5Group(h5Obj, a[[1]]) }, '1' = { getH5Dataset(h5Obj, a[[1]]) })
+
+    if (class(h5Obj) == "H5Dataset") {
+      dim <- getH5Dim(h5Obj)
+    } else {
+      dim <- NA
+    }
+    list(name = a[[1]], type = a[[2]], attributes = .listH5Attributes(h5Obj), dim = dim)
+  })
+  class(lst) <- "H5ContentList"
+  
+  return(lst)
+}
+
+print.H5ContentList <- function(x, ...) {
+  ## This is a pretty way to print the thing, but
+  ## less so to compute on.
+  d <- as.data.frame(do.call(rbind, x))[, -2]
+  print(d)
+}
+  
+
+

Modified: inst/h5_files/ex_1.h5
===================================================================
(Binary files differ)

Modified: inst/h5_files/makeH5.py
===================================================================
--- inst/h5_files/makeH5.py	2010-05-03 18:01:02 UTC (rev 20)
+++ inst/h5_files/makeH5.py	2010-05-04 21:58:29 UTC (rev 21)
@@ -3,9 +3,15 @@
 ##
 import h5py
 from numpy import *
+import os
 
+FILE = "ex_1.h5"
+
+if (os.path.exists(FILE)):
+    os.remove(FILE)
+
 ## file 1
-f = h5py.File("ex_1.h5")
+f = h5py.File(FILE)
 g = f.create_group("group_1")
 m = array([ random.normal(1, 1, 1000) for i in xrange(0, 10) ]).reshape(1000, 10)
 d = g.create_dataset("ds_1", data = m, maxshape = (None, None))
@@ -29,4 +35,11 @@
 a = a.reshape(1000, 10, 5)
 g.create_dataset("ds_7", data = a, maxshape = (None, None, None))
 
+## create some more intricate group structure.
+h = g.create_group("group_2")
+i = h.create_group("group_3")
+
+j = f.create_group("group_4")
+j.create_dataset("ds_1", data = a, maxshape = (None, None, None))
+
 f.close()

Modified: man/H5Obj-class.Rd
===================================================================
--- man/H5Obj-class.Rd	2010-05-03 18:01:02 UTC (rev 20)
+++ man/H5Obj-class.Rd	2010-05-04 21:58:29 UTC (rev 21)
@@ -24,6 +24,8 @@
 \alias{dim,H5DataContainer-method}
 \alias{length,H5DataContainer-method}
 \alias{readSlab}
+\alias{listH5Contents}
+\alias{print.H5ContentList}
 
 \title{Class "H5Obj"}
 \description{Classes for objects originating from HDF5 files.}

Modified: src/h5_wrap.c
===================================================================
--- src/h5_wrap.c	2010-05-03 18:01:02 UTC (rev 20)
+++ src/h5_wrap.c	2010-05-04 21:58:29 UTC (rev 21)
@@ -64,7 +64,7 @@
 	cls_id = H5Aget_type(HID(h5_obj));
 	break;
     default:
-	error("Unkown object in h5R_get_type.");
+	error("Unkown object in %s.\n", __func__);
     }
 
     PROTECT(dtype = ScalarInteger(H5Tget_class(cls_id)));
@@ -85,7 +85,7 @@
 	space = H5Aget_space(HID(h5_obj));
 	break;
     default:
-	error("Unknown object in _h5R_get_space.");
+	error("Unknown object in %s.\n", __func__);
     }
     return space;
 }
@@ -254,7 +254,6 @@
 	Free(buf);
     }
 
-
     /** clean up. **/
     Free(_h_offsets);
     Free(_h_counts);
@@ -267,11 +266,6 @@
 }
 
   
-/** 
- * I am currently keeping read_attr and read_dataset separate because
- * I think that we'll want to separate them in the future to do more
- * complicated things like hyperslab selection.
- */
 SEXP h5R_read_attr(SEXP h5_attr) {
     SEXP dta = R_NilValue;
     hid_t memtype = -1;
@@ -300,5 +294,83 @@
     return dta;
 }
 
+/**
+ * File content iteration.
+ */
+typedef struct __index_and_SEXP__ {
+    int  i;
+    SEXP s;
+} index_and_SEXP;
 
-   
+
+herr_t _h5R_count_func(hid_t loc_id, const char *name, const H5O_info_t *info,
+		       void *operator_data) {
+    int* counter = ((int *) operator_data);
+    (*counter)++;
+    
+    return 0;
+}
+
+herr_t _h5R_capture_name(hid_t loc_id, const char *name, const H5O_info_t *info,
+			 void *operator_data) {
+    index_and_SEXP* od = (index_and_SEXP*) operator_data;
+    SET_STRING_ELT(od->s, (od->i)++, mkChar(name));
+    
+    return 0;
+}
+
+herr_t _h5R_capture_name_and_type(hid_t loc_id, const char *name, const H5O_info_t *info,
+				  void *operator_data) {
+    index_and_SEXP* od = (index_and_SEXP*) operator_data;
+    SEXP lst, str;
+
+    PROTECT(lst = allocVector(VECSXP, 2));
+    PROTECT(str = allocVector(STRSXP, 1));
+    SET_STRING_ELT(str, 0, mkChar(name));
+    SET_VECTOR_ELT(lst, 0, str);
+    SET_VECTOR_ELT(lst, 1, ScalarInteger(info->type));
+    SET_VECTOR_ELT(od->s, (od->i)++, lst);
+
+    UNPROTECT(2);
+
+    return 0;
+}
+
+SEXP h5R_list_contents(SEXP h5_obj) {
+    int counter = 0; 
+    index_and_SEXP* isxp = (index_and_SEXP*) Calloc(1, index_and_SEXP);
+    SEXP dta;
+
+    H5Ovisit (HID(h5_obj), H5_INDEX_NAME, H5_ITER_NATIVE, _h5R_count_func, (void*) &counter);
+
+    PROTECT(dta = allocVector(VECSXP, counter));
+    isxp->s = dta;
+    isxp->i = 0;
+    H5Ovisit (HID(h5_obj), H5_INDEX_NAME, H5_ITER_NATIVE, _h5R_capture_name_and_type, (void*) isxp);
+
+    Free(isxp);
+    UNPROTECT(1);
+
+    return(dta);
+}
+
+SEXP h5R_list_attributes(SEXP h5_obj) {
+    int counter = 0;
+    hsize_t n   = 0;
+    SEXP dta;
+
+    H5Aiterate(HID(h5_obj), H5_INDEX_NAME, H5_ITER_NATIVE, &n, (H5A_operator2_t) _h5R_count_func, (void*) &counter);
+    
+    index_and_SEXP* isxp = (index_and_SEXP*) Calloc(1, index_and_SEXP);
+    PROTECT(dta = allocVector(STRSXP, counter));
+    isxp->s = dta;
+    isxp->i = 0;
+    
+    n = 0;
+    H5Aiterate(HID(h5_obj), H5_INDEX_NAME, H5_ITER_NATIVE, &n, (H5A_operator2_t) _h5R_capture_name, (void*) isxp);
+
+    Free(isxp);
+    UNPROTECT(1);
+
+    return(dta);
+}

Modified: tests/.Rhistory
===================================================================
--- tests/.Rhistory	2010-05-03 18:01:02 UTC (rev 20)
+++ tests/.Rhistory	2010-05-04 21:58:29 UTC (rev 21)
@@ -1,148 +1,150 @@
-files
-g
-slotNames(g)
-getName(g)
-name(g)
-g at name
-for (i,j in c(1,2,3), c(3,4,5)) {
-system.time({1:100})
-system.time({1:100})[1]
-system.time({1:100})[2]
-system.time({1:100})[4]
-TH()
-TH()
-f
-d
-TH()
-dim(d)
-TH()
-assertError(d[,1:12])
-TH()
-ds2
-ds2
-ds2
-ds2[]
-ds2[] == ds2M[]
-all(ds2[] == ds2M[])
-ds2[1:5]
-ds2[1:5] == ds2[1:5]
-ds2M[1:5] == ds2[1:5]
-TH()
-TH
-TH()
-a
-b
 c
-a
-a[]
-b[]
-b[] == 1:7
-oc
-c
-c[]
-c[]
-ds2
-ds2[]
-ds3
-ds3
-ds3[]
-ds3
-ds3[]
-ds3M[]
-xx = ds3[]
-xx[]
-id3
-id3
-f()
-f()
-TH()
-TH()
-TH()
-TH("gg", FALSE)
-TH()
-TH("throw-error")
-source("/home/NANOFLUIDICS/jbullard/projects/software/R/common/h5r/tests/testall.R")
-TH()
-TH(throw-error = TRUE)
-TH(throwError = TRUE)
-TH("a", FALSE)
-TH(throwError = TRUE)
-TH("a", FALSE)
-TH(throwError = TRUE)
-TH
-TH("a", TRUE)
-TH()
-TH(action = "print")
-TH("b", FALSE)
-TH(action = "print")
-TH(action = "throw")
-?tryCatch
-TH("b", FALSE)
-TH(action = "throw")
-TH("b", FALSE)
-TH(action = "throw")
-simpleError()
-simpleError("sdf")
-TH("b", FALSE)
-TH(action = "throw")
-q()
-n
-source("/home/NANOFLUIDICS/jbullard/projects/software/R/common/h5r/tests/testall.R")
-source("/home/NANOFLUIDICS/jbullard/projects/software/R/common/h5r/tests/testall.R")
-TH("aa", FALSE)
-TH(action = "throw")
-TH()
-TH(action = "print")
-dim(ds6
-)
-ds6
-TH(action = "print")
-runif(3, c(1,2,3), c(2,3,4))
-ls()
-b
-d
-ds2
-ds4
-ds4[1:3, 1:2]
-ds4[1:2, 1]
-call(ds4[1:2, 1])
-expression(ds4[1:2, 1])
-substitute(ds4[1:2, 1])
-as.call(ds4[1:2, 1])
-?call
-call("[", ds4, 1:2, 1)
-eval(call("[", ds4, 1:2, 1))
-eval(call("[", ds4, list(1:2, 1)))
-eval(call("[", ds4, 1:2, 1))
-call("[", ds4, 1:2, 1)
-as.call(call("[", ds4, 1:2, 1))
-as.list(call("[", ds4, 1:2, 1))
-as.call(as.list(call("[", ds4, 1:2, 1)))
-as.list(call("[", ds4))
-xx = as.list(call("[", ds4))
-xx[[3]] <- 1:2
-xx[[4]] <- 1
-xx
-as.call(xx)
-eval(as.call(xx))
-randomSlice(ds2)
-randomSlice(ds2)
-randomSlice(ds2)
-n
-dims
-ds2
-Q
-ls()
-ds4
 randomSlice(ds4)
-c
 randomSlice(ds4)
 randomSlice(ds4)
 randomSlice(ds4)
 randomSlice(ds4)
 randomSlice(ds4)
-randomSlice(ds4)
 replicate(100, randomSlice(ds4))
 q()
 n
 ds7
+TH(action="print"0
+TH(action="print")
+a
+sapply(a, dim)
+source("/home/NANOFLUIDICS/jbullard/projects/software/R/common/h5r/tests/testall.R")
+.Call("h5R_get_contents", f)
+slotNames(f)
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", g at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+1
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+1
+.Call("h5R_get_contents", f at ePtr)
+1
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+4
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+f
+.Call("h5R_get_contents", f at ePtr)
+.Call("h5R_get_contents", f at ePtr)
+gc()
+x = replicate(10000, .Call("h5R_get_contents", f at ePtr))
+rm(x)
+gc()
+x = replicate(1000000, .Call("h5R_get_contents", f at ePtr))
+rm(x)
+gc()
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+.Call("h5R_get_contents", f at ePtr)
+x = .Call("h5R_get_contents", f at ePtr)
+x[[1]]
+x[[1]][[1]]
+as.character(x[[1]][[1]])
+as.string(x[[1]][[1]])
+require(h5r)
+x = .Call("h5R_get_contents", f at ePtr)
+x
+.Call("h5R_get_contents", f at ePtr)
+require(h5r)
+x = getH5Dataset(f, "ds_2")
+1
+require(h5r)
+x = getH5Dataset(f, "ds_2")
+x = getH5Dataset(g, "ds_2")
+x
+.Call(x at ePtr, "h5R_get_attributes")
+x at ePter
+x at ePtr
+.Call(x at ePtr, "h5R_get_attributes")
+x
+ getH5Attribute(x, "x")
+ getH5Attribute(x, "x")[]
+.Call(x at ePtr, "h5R_get_attributes")
+require(h5r)
+x = getH5Dataset(g, "ds_2")
+.Call(x at ePtr, "h5R_get_attributes")
+.Call(x at ePtr, "h5R_get_attributes", PACKAGE = "h5r")
+x at ePtr
+getH5Dims(x)
+getH5Dim(x)
+.Call("h5R_get_attributes", x at ePtr)
+require(h5r)
+x = getH5Dataset(g, "ds_2")
+.Call("h5R_get_attributes", x at ePtr)
+.Call("h5R_get_attributes", x at ePtr)
+.Call("h5R_get_attributes", x at ePtr)
+x = getH5Dataset(g, "ds_2")
+require(h5r)
+x = getH5Dataset(g, "ds_2")
+x
+getH5Attribute(x, "x")
+.Call("h5R_get_attributes", x at ePtr)
+require(h5r)
+getH5Attribute(x, "x")
+x = getH5Dataset(g, "ds_2")
+.Call("h5R_get_attributes", x at ePtr)
+require(h5r)
+x = getH5Dataset(g, "ds_2")
+.Call("h5R_get_attributes", x at ePtr)
+.Call("h5R_get_attributes", x at ePtr)
+.Call("h5R_get_attributes", x at ePtr)
+.Call("h5R_get_attributes", ds1 at ePtr)
+.Call("h5R_get_attributes", g at ePtr)
+ls
+?ls
+g
+listH5Attributes(g)
+listH5Contents(g)
+a[[1]]
+contents
+n
+a[[1]]
+getH5Group(a[[1]])
+getH5Group(f, a[[1]])
+Q
+n
+a[[1]]
+getH5Group(a[[1]], f)
+getH5Group(f, a[[1]])
+a[[2]]
+h5Obj
+h5Obj
+Q
+lst
+do.call(rbind, lst)
+as.data.frame(do.call(rbind, lst))
+print
+f
+listH5Contents(f)
+listH5Contents(f)
+f
+listH5Contents(f)
+s = listH5Contents(f)
+s
+s = listH5Contents(f)
+s
+as.list(s)
+s[]
+s
+q()
+n



More information about the H5r-commits mailing list