[R] native routines registration (#2290)
* [R] add native routines registration * c_api.h needs to include <cstdint> since it uses fixed width integer types * [R] use registered native routines from R code * [R] bump version; add info on native routine registration to the contributors guide * make lint happy
This commit is contained in:
parent
6bd1869026
commit
c66ca79221
@ -1,7 +1,7 @@
|
|||||||
Package: xgboost
|
Package: xgboost
|
||||||
Type: Package
|
Type: Package
|
||||||
Title: Extreme Gradient Boosting
|
Title: Extreme Gradient Boosting
|
||||||
Version: 0.6.4.3
|
Version: 0.6.4.4
|
||||||
Date: 2017-01-04
|
Date: 2017-01-04
|
||||||
Author: Tianqi Chen <tianqi.tchen@gmail.com>, Tong He <hetong007@gmail.com>,
|
Author: Tianqi Chen <tianqi.tchen@gmail.com>, Tong He <hetong007@gmail.com>,
|
||||||
Michael Benesty <michael@benesty.fr>, Vadim Khotilovich <khotilovich@gmail.com>,
|
Michael Benesty <michael@benesty.fr>, Vadim Khotilovich <khotilovich@gmail.com>,
|
||||||
|
|||||||
@ -76,4 +76,4 @@ importFrom(utils,head)
|
|||||||
importFrom(utils,object.size)
|
importFrom(utils,object.size)
|
||||||
importFrom(utils,str)
|
importFrom(utils,str)
|
||||||
importFrom(utils,tail)
|
importFrom(utils,tail)
|
||||||
useDynLib(xgboost)
|
useDynLib(xgboost, .registration = TRUE)
|
||||||
|
|||||||
@ -130,12 +130,11 @@ xgb.iter.update <- function(booster_handle, dtrain, iter, obj = NULL) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
if (is.null(obj)) {
|
if (is.null(obj)) {
|
||||||
.Call("XGBoosterUpdateOneIter_R", booster_handle, as.integer(iter), dtrain,
|
.Call(XGBoosterUpdateOneIter_R, booster_handle, as.integer(iter), dtrain)
|
||||||
PACKAGE = "xgboost")
|
|
||||||
} else {
|
} else {
|
||||||
pred <- predict(booster_handle, dtrain)
|
pred <- predict(booster_handle, dtrain)
|
||||||
gpair <- obj(pred, dtrain)
|
gpair <- obj(pred, dtrain)
|
||||||
.Call("XGBoosterBoostOneIter_R", booster_handle, dtrain, gpair$grad, gpair$hess, PACKAGE = "xgboost")
|
.Call(XGBoosterBoostOneIter_R, booster_handle, dtrain, gpair$grad, gpair$hess)
|
||||||
}
|
}
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
@ -153,8 +152,7 @@ xgb.iter.eval <- function(booster_handle, watchlist, iter, feval = NULL) {
|
|||||||
|
|
||||||
evnames <- names(watchlist)
|
evnames <- names(watchlist)
|
||||||
if (is.null(feval)) {
|
if (is.null(feval)) {
|
||||||
msg <- .Call("XGBoosterEvalOneIter_R", booster_handle, as.integer(iter), watchlist,
|
msg <- .Call(XGBoosterEvalOneIter_R, booster_handle, as.integer(iter), watchlist, as.list(evnames))
|
||||||
as.list(evnames), PACKAGE = "xgboost")
|
|
||||||
msg <- stri_split_regex(msg, '(\\s+|:|\\s+)')[[1]][-1]
|
msg <- stri_split_regex(msg, '(\\s+|:|\\s+)')[[1]][-1]
|
||||||
res <- as.numeric(msg[c(FALSE,TRUE)]) # even indices are the values
|
res <- as.numeric(msg[c(FALSE,TRUE)]) # even indices are the values
|
||||||
names(res) <- msg[c(TRUE,FALSE)] # odds are the names
|
names(res) <- msg[c(TRUE,FALSE)] # odds are the names
|
||||||
|
|||||||
@ -6,15 +6,15 @@ xgb.Booster.handle <- function(params = list(), cachelist = list(), modelfile =
|
|||||||
stop("cachelist must be a list of xgb.DMatrix objects")
|
stop("cachelist must be a list of xgb.DMatrix objects")
|
||||||
}
|
}
|
||||||
|
|
||||||
handle <- .Call("XGBoosterCreate_R", cachelist, PACKAGE = "xgboost")
|
handle <- .Call(XGBoosterCreate_R, cachelist)
|
||||||
if (!is.null(modelfile)) {
|
if (!is.null(modelfile)) {
|
||||||
if (typeof(modelfile) == "character") {
|
if (typeof(modelfile) == "character") {
|
||||||
.Call("XGBoosterLoadModel_R", handle, modelfile[1], PACKAGE = "xgboost")
|
.Call(XGBoosterLoadModel_R, handle, modelfile[1])
|
||||||
} else if (typeof(modelfile) == "raw") {
|
} else if (typeof(modelfile) == "raw") {
|
||||||
.Call("XGBoosterLoadModelFromRaw_R", handle, modelfile, PACKAGE = "xgboost")
|
.Call(XGBoosterLoadModelFromRaw_R, handle, modelfile)
|
||||||
} else if (inherits(modelfile, "xgb.Booster")) {
|
} else if (inherits(modelfile, "xgb.Booster")) {
|
||||||
bst <- xgb.Booster.complete(modelfile, saveraw = TRUE)
|
bst <- xgb.Booster.complete(modelfile, saveraw = TRUE)
|
||||||
.Call("XGBoosterLoadModelFromRaw_R", handle, bst$raw, PACKAGE = "xgboost")
|
.Call(XGBoosterLoadModelFromRaw_R, handle, bst$raw)
|
||||||
} else {
|
} else {
|
||||||
stop("modelfile must be either character filename, or raw booster dump, or xgb.Booster object")
|
stop("modelfile must be either character filename, or raw booster dump, or xgb.Booster object")
|
||||||
}
|
}
|
||||||
@ -40,7 +40,7 @@ is.null.handle <- function(handle) {
|
|||||||
if (!identical(class(handle), "xgb.Booster.handle"))
|
if (!identical(class(handle), "xgb.Booster.handle"))
|
||||||
stop("argument type must be xgb.Booster.handle")
|
stop("argument type must be xgb.Booster.handle")
|
||||||
|
|
||||||
if (is.null(handle) || .Call("XGCheckNullPtr_R", handle, PACKAGE = "xgboost"))
|
if (is.null(handle) || .Call(XGCheckNullPtr_R, handle))
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
return(FALSE)
|
return(FALSE)
|
||||||
}
|
}
|
||||||
@ -237,8 +237,7 @@ predict.xgb.Booster <- function(object, newdata, missing = NA,
|
|||||||
|
|
||||||
option <- 0L + 1L * as.logical(outputmargin) + 2L * as.logical(predleaf)
|
option <- 0L + 1L * as.logical(outputmargin) + 2L * as.logical(predleaf)
|
||||||
|
|
||||||
ret <- .Call("XGBoosterPredict_R", object$handle, newdata, option[1],
|
ret <- .Call(XGBoosterPredict_R, object$handle, newdata, option[1], as.integer(ntreelimit))
|
||||||
as.integer(ntreelimit), PACKAGE = "xgboost")
|
|
||||||
|
|
||||||
if (length(ret) %% nrow(newdata) != 0)
|
if (length(ret) %% nrow(newdata) != 0)
|
||||||
stop("prediction length ", length(ret)," is not multiple of nrows(newdata) ", nrow(newdata))
|
stop("prediction length ", length(ret)," is not multiple of nrows(newdata) ", nrow(newdata))
|
||||||
@ -338,7 +337,7 @@ predict.xgb.Booster.handle <- function(object, ...) {
|
|||||||
xgb.attr <- function(object, name) {
|
xgb.attr <- function(object, name) {
|
||||||
if (is.null(name) || nchar(as.character(name[1])) == 0) stop("invalid attribute name")
|
if (is.null(name) || nchar(as.character(name[1])) == 0) stop("invalid attribute name")
|
||||||
handle <- xgb.get.handle(object)
|
handle <- xgb.get.handle(object)
|
||||||
.Call("XGBoosterGetAttr_R", handle, as.character(name[1]), PACKAGE = "xgboost")
|
.Call(XGBoosterGetAttr_R, handle, as.character(name[1]))
|
||||||
}
|
}
|
||||||
|
|
||||||
#' @rdname xgb.attr
|
#' @rdname xgb.attr
|
||||||
@ -355,7 +354,7 @@ xgb.attr <- function(object, name) {
|
|||||||
value <- as.character(value[1])
|
value <- as.character(value[1])
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
.Call("XGBoosterSetAttr_R", handle, as.character(name[1]), value, PACKAGE = "xgboost")
|
.Call(XGBoosterSetAttr_R, handle, as.character(name[1]), value)
|
||||||
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
||||||
object$raw <- xgb.save.raw(object$handle)
|
object$raw <- xgb.save.raw(object$handle)
|
||||||
}
|
}
|
||||||
@ -366,10 +365,10 @@ xgb.attr <- function(object, name) {
|
|||||||
#' @export
|
#' @export
|
||||||
xgb.attributes <- function(object) {
|
xgb.attributes <- function(object) {
|
||||||
handle <- xgb.get.handle(object)
|
handle <- xgb.get.handle(object)
|
||||||
attr_names <- .Call("XGBoosterGetAttrNames_R", handle, PACKAGE = "xgboost")
|
attr_names <- .Call(XGBoosterGetAttrNames_R, handle)
|
||||||
if (is.null(attr_names)) return(NULL)
|
if (is.null(attr_names)) return(NULL)
|
||||||
res <- lapply(attr_names, function(x) {
|
res <- lapply(attr_names, function(x) {
|
||||||
.Call("XGBoosterGetAttr_R", handle, x, PACKAGE = "xgboost")
|
.Call(XGBoosterGetAttr_R, handle, x)
|
||||||
})
|
})
|
||||||
names(res) <- attr_names
|
names(res) <- attr_names
|
||||||
res
|
res
|
||||||
@ -394,7 +393,7 @@ xgb.attributes <- function(object) {
|
|||||||
})
|
})
|
||||||
handle <- xgb.get.handle(object)
|
handle <- xgb.get.handle(object)
|
||||||
for (i in seq_along(a)) {
|
for (i in seq_along(a)) {
|
||||||
.Call("XGBoosterSetAttr_R", handle, names(a[i]), a[[i]], PACKAGE = "xgboost")
|
.Call(XGBoosterSetAttr_R, handle, names(a[i]), a[[i]])
|
||||||
}
|
}
|
||||||
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
||||||
object$raw <- xgb.save.raw(object$handle)
|
object$raw <- xgb.save.raw(object$handle)
|
||||||
@ -435,7 +434,7 @@ xgb.attributes <- function(object) {
|
|||||||
p <- lapply(p, function(x) as.character(x)[1])
|
p <- lapply(p, function(x) as.character(x)[1])
|
||||||
handle <- xgb.get.handle(object)
|
handle <- xgb.get.handle(object)
|
||||||
for (i in seq_along(p)) {
|
for (i in seq_along(p)) {
|
||||||
.Call("XGBoosterSetParam_R", handle, names(p[i]), p[[i]], PACKAGE = "xgboost")
|
.Call(XGBoosterSetParam_R, handle, names(p[i]), p[[i]])
|
||||||
}
|
}
|
||||||
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
if (is(object, 'xgb.Booster') && !is.null(object$raw)) {
|
||||||
object$raw <- xgb.save.raw(object$handle)
|
object$raw <- xgb.save.raw(object$handle)
|
||||||
|
|||||||
@ -26,15 +26,12 @@ xgb.DMatrix <- function(data, info = list(), missing = NA, silent = FALSE, ...)
|
|||||||
if (length(data) > 1)
|
if (length(data) > 1)
|
||||||
stop("'data' has class 'character' and length ", length(data),
|
stop("'data' has class 'character' and length ", length(data),
|
||||||
".\n 'data' accepts either a numeric matrix or a single filename.")
|
".\n 'data' accepts either a numeric matrix or a single filename.")
|
||||||
handle <- .Call("XGDMatrixCreateFromFile_R", data, as.integer(silent),
|
handle <- .Call(XGDMatrixCreateFromFile_R, data, as.integer(silent))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
} else if (is.matrix(data)) {
|
} else if (is.matrix(data)) {
|
||||||
handle <- .Call("XGDMatrixCreateFromMat_R", data, missing,
|
handle <- .Call(XGDMatrixCreateFromMat_R, data, missing)
|
||||||
PACKAGE = "xgboost")
|
|
||||||
cnames <- colnames(data)
|
cnames <- colnames(data)
|
||||||
} else if (inherits(data, "dgCMatrix")) {
|
} else if (inherits(data, "dgCMatrix")) {
|
||||||
handle <- .Call("XGDMatrixCreateFromCSC_R", data@p, data@i, data@x, nrow(data),
|
handle <- .Call(XGDMatrixCreateFromCSC_R, data@p, data@i, data@x, nrow(data))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
cnames <- colnames(data)
|
cnames <- colnames(data)
|
||||||
} else {
|
} else {
|
||||||
stop("xgb.DMatrix does not support construction from ", typeof(data))
|
stop("xgb.DMatrix does not support construction from ", typeof(data))
|
||||||
@ -100,8 +97,7 @@ xgb.get.DMatrix <- function(data, label = NULL, missing = NA, weight = NULL) {
|
|||||||
#'
|
#'
|
||||||
#' @export
|
#' @export
|
||||||
dim.xgb.DMatrix <- function(x) {
|
dim.xgb.DMatrix <- function(x) {
|
||||||
c(.Call("XGDMatrixNumRow_R", x, PACKAGE = "xgboost"),
|
c(.Call(XGDMatrixNumRow_R, x), .Call(XGDMatrixNumCol_R, x))
|
||||||
.Call("XGDMatrixNumCol_R", x, PACKAGE = "xgboost"))
|
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
@ -193,7 +189,7 @@ getinfo.xgb.DMatrix <- function(object, name, ...) {
|
|||||||
" 'label', 'weight', 'base_margin', 'nrow'")
|
" 'label', 'weight', 'base_margin', 'nrow'")
|
||||||
}
|
}
|
||||||
if (name != "nrow"){
|
if (name != "nrow"){
|
||||||
ret <- .Call("XGDMatrixGetInfo_R", object, name, PACKAGE = "xgboost")
|
ret <- .Call(XGDMatrixGetInfo_R, object, name)
|
||||||
} else {
|
} else {
|
||||||
ret <- nrow(object)
|
ret <- nrow(object)
|
||||||
}
|
}
|
||||||
@ -240,29 +236,25 @@ setinfo.xgb.DMatrix <- function(object, name, info, ...) {
|
|||||||
if (name == "label") {
|
if (name == "label") {
|
||||||
if (length(info) != nrow(object))
|
if (length(info) != nrow(object))
|
||||||
stop("The length of labels must equal to the number of rows in the input data")
|
stop("The length of labels must equal to the number of rows in the input data")
|
||||||
.Call("XGDMatrixSetInfo_R", object, name, as.numeric(info),
|
.Call(XGDMatrixSetInfo_R, object, name, as.numeric(info))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
if (name == "weight") {
|
if (name == "weight") {
|
||||||
if (length(info) != nrow(object))
|
if (length(info) != nrow(object))
|
||||||
stop("The length of weights must equal to the number of rows in the input data")
|
stop("The length of weights must equal to the number of rows in the input data")
|
||||||
.Call("XGDMatrixSetInfo_R", object, name, as.numeric(info),
|
.Call(XGDMatrixSetInfo_R, object, name, as.numeric(info))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
if (name == "base_margin") {
|
if (name == "base_margin") {
|
||||||
# if (length(info)!=nrow(object))
|
# if (length(info)!=nrow(object))
|
||||||
# stop("The length of base margin must equal to the number of rows in the input data")
|
# stop("The length of base margin must equal to the number of rows in the input data")
|
||||||
.Call("XGDMatrixSetInfo_R", object, name, as.numeric(info),
|
.Call(XGDMatrixSetInfo_R, object, name, as.numeric(info))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
if (name == "group") {
|
if (name == "group") {
|
||||||
if (sum(info) != nrow(object))
|
if (sum(info) != nrow(object))
|
||||||
stop("The sum of groups must equal to the number of rows in the input data")
|
stop("The sum of groups must equal to the number of rows in the input data")
|
||||||
.Call("XGDMatrixSetInfo_R", object, name, as.integer(info),
|
.Call(XGDMatrixSetInfo_R, object, name, as.integer(info))
|
||||||
PACKAGE = "xgboost")
|
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
stop("setinfo: unknown info name ", name)
|
stop("setinfo: unknown info name ", name)
|
||||||
@ -302,7 +294,7 @@ slice.xgb.DMatrix <- function(object, idxset, ...) {
|
|||||||
if (!inherits(object, "xgb.DMatrix")) {
|
if (!inherits(object, "xgb.DMatrix")) {
|
||||||
stop("object must be xgb.DMatrix")
|
stop("object must be xgb.DMatrix")
|
||||||
}
|
}
|
||||||
ret <- .Call("XGDMatrixSliceDMatrix_R", object, idxset, PACKAGE = "xgboost")
|
ret <- .Call(XGDMatrixSliceDMatrix_R, object, idxset)
|
||||||
|
|
||||||
attr_list <- attributes(object)
|
attr_list <- attributes(object)
|
||||||
nr <- nrow(object)
|
nr <- nrow(object)
|
||||||
|
|||||||
@ -18,6 +18,6 @@ xgb.DMatrix.save <- function(dmatrix, fname) {
|
|||||||
if (!inherits(dmatrix, "xgb.DMatrix"))
|
if (!inherits(dmatrix, "xgb.DMatrix"))
|
||||||
stop("dmatrix must be xgb.DMatrix")
|
stop("dmatrix must be xgb.DMatrix")
|
||||||
|
|
||||||
.Call("XGDMatrixSaveBinary_R", dmatrix, fname[1], 0L, PACKAGE = "xgboost")
|
.Call(XGDMatrixSaveBinary_R, dmatrix, fname[1], 0L)
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -51,8 +51,8 @@ xgb.dump <- function(model, fname = NULL, fmap = "", with_stats=FALSE,
|
|||||||
stop("fmap: argument must be a character string (when provided)")
|
stop("fmap: argument must be a character string (when provided)")
|
||||||
|
|
||||||
model <- xgb.Booster.complete(model)
|
model <- xgb.Booster.complete(model)
|
||||||
model_dump <- .Call("XGBoosterDumpModel_R", model$handle, NVL(fmap, "")[1], as.integer(with_stats),
|
model_dump <- .Call(XGBoosterDumpModel_R, model$handle, NVL(fmap, "")[1], as.integer(with_stats),
|
||||||
as.character(dump_format), PACKAGE = "xgboost")
|
as.character(dump_format))
|
||||||
|
|
||||||
if (is.null(fname))
|
if (is.null(fname))
|
||||||
model_dump <- stri_replace_all_regex(model_dump, '\t', '')
|
model_dump <- stri_replace_all_regex(model_dump, '\t', '')
|
||||||
|
|||||||
@ -37,6 +37,6 @@ xgb.save <- function(model, fname) {
|
|||||||
if (inherits(model, "xgb.DMatrix")) " Use xgb.DMatrix.save to save an xgb.DMatrix object." else "")
|
if (inherits(model, "xgb.DMatrix")) " Use xgb.DMatrix.save to save an xgb.DMatrix object." else "")
|
||||||
}
|
}
|
||||||
model <- xgb.Booster.complete(model, saveraw = FALSE)
|
model <- xgb.Booster.complete(model, saveraw = FALSE)
|
||||||
.Call("XGBoosterSaveModel_R", model$handle, fname[1], PACKAGE = "xgboost")
|
.Call(XGBoosterSaveModel_R, model$handle, fname[1])
|
||||||
return(TRUE)
|
return(TRUE)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -19,5 +19,5 @@
|
|||||||
#' @export
|
#' @export
|
||||||
xgb.save.raw <- function(model) {
|
xgb.save.raw <- function(model) {
|
||||||
model <- xgb.get.handle(model)
|
model <- xgb.get.handle(model)
|
||||||
.Call("XGBoosterModelToRaw_R", model, PACKAGE = "xgboost")
|
.Call(XGBoosterModelToRaw_R, model)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -105,5 +105,5 @@ NULL
|
|||||||
#' @importFrom graphics title
|
#' @importFrom graphics title
|
||||||
#'
|
#'
|
||||||
#' @import methods
|
#' @import methods
|
||||||
#' @useDynLib xgboost
|
#' @useDynLib xgboost, .registration = TRUE
|
||||||
NULL
|
NULL
|
||||||
|
|||||||
@ -13,6 +13,6 @@ XGB_RFLAGS = -DXGBOOST_STRICT_R_MODE=1 -DDMLC_LOG_BEFORE_THROW=0\
|
|||||||
PKG_CPPFLAGS= -I$(PKGROOT)/include -I$(PKGROOT)/dmlc-core/include -I$(PKGROOT)/rabit/include -I$(PKGROOT) $(XGB_RFLAGS)
|
PKG_CPPFLAGS= -I$(PKGROOT)/include -I$(PKGROOT)/dmlc-core/include -I$(PKGROOT)/rabit/include -I$(PKGROOT) $(XGB_RFLAGS)
|
||||||
PKG_CXXFLAGS= @OPENMP_CXXFLAGS@ $(SHLIB_PTHREAD_FLAGS)
|
PKG_CXXFLAGS= @OPENMP_CXXFLAGS@ $(SHLIB_PTHREAD_FLAGS)
|
||||||
PKG_LIBS = @OPENMP_CXXFLAGS@ $(SHLIB_PTHREAD_FLAGS)
|
PKG_LIBS = @OPENMP_CXXFLAGS@ $(SHLIB_PTHREAD_FLAGS)
|
||||||
OBJECTS= ./xgboost_R.o ./xgboost_custom.o ./xgboost_assert.o\
|
OBJECTS= ./xgboost_R.o ./xgboost_custom.o ./xgboost_assert.o ./init.o\
|
||||||
$(PKGROOT)/amalgamation/xgboost-all0.o $(PKGROOT)/amalgamation/dmlc-minimum0.o\
|
$(PKGROOT)/amalgamation/xgboost-all0.o $(PKGROOT)/amalgamation/dmlc-minimum0.o\
|
||||||
$(PKGROOT)/rabit/src/engine_empty.o $(PKGROOT)/rabit/src/c_api.o
|
$(PKGROOT)/rabit/src/engine_empty.o $(PKGROOT)/rabit/src/c_api.o
|
||||||
|
|||||||
@ -25,7 +25,7 @@ XGB_RFLAGS = -DXGBOOST_STRICT_R_MODE=1 -DDMLC_LOG_BEFORE_THROW=0\
|
|||||||
PKG_CPPFLAGS= -I$(PKGROOT)/include -I$(PKGROOT)/dmlc-core/include -I$(PKGROOT)/rabit/include -I$(PKGROOT) $(XGB_RFLAGS)
|
PKG_CPPFLAGS= -I$(PKGROOT)/include -I$(PKGROOT)/dmlc-core/include -I$(PKGROOT)/rabit/include -I$(PKGROOT) $(XGB_RFLAGS)
|
||||||
PKG_CXXFLAGS= $(SHLIB_OPENMP_CFLAGS) $(SHLIB_PTHREAD_FLAGS)
|
PKG_CXXFLAGS= $(SHLIB_OPENMP_CFLAGS) $(SHLIB_PTHREAD_FLAGS)
|
||||||
PKG_LIBS = $(SHLIB_OPENMP_CFLAGS) $(SHLIB_PTHREAD_FLAGS)
|
PKG_LIBS = $(SHLIB_OPENMP_CFLAGS) $(SHLIB_PTHREAD_FLAGS)
|
||||||
OBJECTS= ./xgboost_R.o ./xgboost_custom.o ./xgboost_assert.o\
|
OBJECTS= ./xgboost_R.o ./xgboost_custom.o ./xgboost_assert.o ./init.o\
|
||||||
$(PKGROOT)/amalgamation/xgboost-all0.o $(PKGROOT)/amalgamation/dmlc-minimum0.o\
|
$(PKGROOT)/amalgamation/xgboost-all0.o $(PKGROOT)/amalgamation/dmlc-minimum0.o\
|
||||||
$(PKGROOT)/rabit/src/engine_empty.o $(PKGROOT)/rabit/src/c_api.o
|
$(PKGROOT)/rabit/src/engine_empty.o $(PKGROOT)/rabit/src/c_api.o
|
||||||
|
|
||||||
|
|||||||
74
R-package/src/init.c
Normal file
74
R-package/src/init.c
Normal file
@ -0,0 +1,74 @@
|
|||||||
|
/* Copyright (c) 2015 by Contributors
|
||||||
|
*
|
||||||
|
* This file was initially generated using the following R command:
|
||||||
|
* tools::package_native_routine_registration_skeleton('.', con = 'src/init.c', character_only = F)
|
||||||
|
* and edited to conform to xgboost C linter requirements. For details, see
|
||||||
|
* https://cran.r-project.org/doc/manuals/r-release/R-exts.html#Registering-native-routines
|
||||||
|
*/
|
||||||
|
#include <R.h>
|
||||||
|
#include <Rinternals.h>
|
||||||
|
#include <stdlib.h>
|
||||||
|
#include <R_ext/Rdynload.h>
|
||||||
|
|
||||||
|
/* FIXME:
|
||||||
|
Check these declarations against the C/Fortran source code.
|
||||||
|
*/
|
||||||
|
|
||||||
|
/* .Call calls */
|
||||||
|
extern SEXP XGBoosterBoostOneIter_R(SEXP, SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterCreate_R(SEXP);
|
||||||
|
extern SEXP XGBoosterDumpModel_R(SEXP, SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterEvalOneIter_R(SEXP, SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterGetAttr_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterGetAttrNames_R(SEXP);
|
||||||
|
extern SEXP XGBoosterLoadModel_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterLoadModelFromRaw_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterModelToRaw_R(SEXP);
|
||||||
|
extern SEXP XGBoosterPredict_R(SEXP, SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterSaveModel_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterSetAttr_R(SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterSetParam_R(SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGBoosterUpdateOneIter_R(SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGCheckNullPtr_R(SEXP);
|
||||||
|
extern SEXP XGDMatrixCreateFromCSC_R(SEXP, SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixCreateFromFile_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixCreateFromMat_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixGetInfo_R(SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixNumCol_R(SEXP);
|
||||||
|
extern SEXP XGDMatrixNumRow_R(SEXP);
|
||||||
|
extern SEXP XGDMatrixSaveBinary_R(SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixSetInfo_R(SEXP, SEXP, SEXP);
|
||||||
|
extern SEXP XGDMatrixSliceDMatrix_R(SEXP, SEXP);
|
||||||
|
|
||||||
|
static const R_CallMethodDef CallEntries[] = {
|
||||||
|
{"XGBoosterBoostOneIter_R", (DL_FUNC) &XGBoosterBoostOneIter_R, 4},
|
||||||
|
{"XGBoosterCreate_R", (DL_FUNC) &XGBoosterCreate_R, 1},
|
||||||
|
{"XGBoosterDumpModel_R", (DL_FUNC) &XGBoosterDumpModel_R, 4},
|
||||||
|
{"XGBoosterEvalOneIter_R", (DL_FUNC) &XGBoosterEvalOneIter_R, 4},
|
||||||
|
{"XGBoosterGetAttr_R", (DL_FUNC) &XGBoosterGetAttr_R, 2},
|
||||||
|
{"XGBoosterGetAttrNames_R", (DL_FUNC) &XGBoosterGetAttrNames_R, 1},
|
||||||
|
{"XGBoosterLoadModel_R", (DL_FUNC) &XGBoosterLoadModel_R, 2},
|
||||||
|
{"XGBoosterLoadModelFromRaw_R", (DL_FUNC) &XGBoosterLoadModelFromRaw_R, 2},
|
||||||
|
{"XGBoosterModelToRaw_R", (DL_FUNC) &XGBoosterModelToRaw_R, 1},
|
||||||
|
{"XGBoosterPredict_R", (DL_FUNC) &XGBoosterPredict_R, 4},
|
||||||
|
{"XGBoosterSaveModel_R", (DL_FUNC) &XGBoosterSaveModel_R, 2},
|
||||||
|
{"XGBoosterSetAttr_R", (DL_FUNC) &XGBoosterSetAttr_R, 3},
|
||||||
|
{"XGBoosterSetParam_R", (DL_FUNC) &XGBoosterSetParam_R, 3},
|
||||||
|
{"XGBoosterUpdateOneIter_R", (DL_FUNC) &XGBoosterUpdateOneIter_R, 3},
|
||||||
|
{"XGCheckNullPtr_R", (DL_FUNC) &XGCheckNullPtr_R, 1},
|
||||||
|
{"XGDMatrixCreateFromCSC_R", (DL_FUNC) &XGDMatrixCreateFromCSC_R, 4},
|
||||||
|
{"XGDMatrixCreateFromFile_R", (DL_FUNC) &XGDMatrixCreateFromFile_R, 2},
|
||||||
|
{"XGDMatrixCreateFromMat_R", (DL_FUNC) &XGDMatrixCreateFromMat_R, 2},
|
||||||
|
{"XGDMatrixGetInfo_R", (DL_FUNC) &XGDMatrixGetInfo_R, 2},
|
||||||
|
{"XGDMatrixNumCol_R", (DL_FUNC) &XGDMatrixNumCol_R, 1},
|
||||||
|
{"XGDMatrixNumRow_R", (DL_FUNC) &XGDMatrixNumRow_R, 1},
|
||||||
|
{"XGDMatrixSaveBinary_R", (DL_FUNC) &XGDMatrixSaveBinary_R, 3},
|
||||||
|
{"XGDMatrixSetInfo_R", (DL_FUNC) &XGDMatrixSetInfo_R, 3},
|
||||||
|
{"XGDMatrixSliceDMatrix_R", (DL_FUNC) &XGDMatrixSliceDMatrix_R, 2},
|
||||||
|
{NULL, NULL, 0}
|
||||||
|
};
|
||||||
|
|
||||||
|
void R_init_xgboost(DllInfo *dll) {
|
||||||
|
R_registerRoutines(dll, NULL, CallEntries, NULL, NULL);
|
||||||
|
R_useDynamicSymbols(dll, FALSE);
|
||||||
|
}
|
||||||
@ -158,3 +158,7 @@ Some additional consideration is needed when the core library version changes.
|
|||||||
E.g., after the core changes from 0.6 to 0.7, the R package development version would become 0.7.0.1, working towards
|
E.g., after the core changes from 0.6 to 0.7, the R package development version would become 0.7.0.1, working towards
|
||||||
a 0.7.1 CRAN release. The 0.7.0 would not be released to CRAN, unless it would require almost no additional development.
|
a 0.7.1 CRAN release. The 0.7.0 would not be released to CRAN, unless it would require almost no additional development.
|
||||||
|
|
||||||
|
### Registering native routines in R
|
||||||
|
According to [R extension manual](https://cran.r-project.org/doc/manuals/r-release/R-exts.html#Registering-native-routines),
|
||||||
|
it is good practice to register native routines and to disable symbol search. When any changes or additions are made to the
|
||||||
|
C++ interface of the R package, please make corresponding changes in ```src/init.c``` as well.
|
||||||
|
|||||||
@ -2,11 +2,13 @@
|
|||||||
* Copyright (c) 2015 by Contributors
|
* Copyright (c) 2015 by Contributors
|
||||||
* \file c_api.h
|
* \file c_api.h
|
||||||
* \author Tianqi Chen
|
* \author Tianqi Chen
|
||||||
* \brief C API of XGBoost, used to interfacing with other languages.
|
* \brief C API of XGBoost, used for interfacing to other languages.
|
||||||
*/
|
*/
|
||||||
#ifndef XGBOOST_C_API_H_
|
#ifndef XGBOOST_C_API_H_
|
||||||
#define XGBOOST_C_API_H_
|
#define XGBOOST_C_API_H_
|
||||||
|
|
||||||
|
#include <cstdint>
|
||||||
|
|
||||||
#ifdef __cplusplus
|
#ifdef __cplusplus
|
||||||
#define XGB_EXTERN_C extern "C"
|
#define XGB_EXTERN_C extern "C"
|
||||||
#endif
|
#endif
|
||||||
@ -62,7 +64,7 @@ typedef struct {
|
|||||||
/*!
|
/*!
|
||||||
* \brief Callback to set the data to handle,
|
* \brief Callback to set the data to handle,
|
||||||
* \param handle The handle to the callback.
|
* \param handle The handle to the callback.
|
||||||
* \param batch The data content to be setted.
|
* \param batch The data content to be set.
|
||||||
*/
|
*/
|
||||||
XGB_EXTERN_C typedef int XGBCallbackSetData(
|
XGB_EXTERN_C typedef int XGBCallbackSetData(
|
||||||
DataHolderHandle handle, XGBoostBatchCSR batch);
|
DataHolderHandle handle, XGBoostBatchCSR batch);
|
||||||
|
|||||||
Loading…
x
Reference in New Issue
Block a user