diff --git a/R-proj/R/RcppExports.R b/R-proj/R/RcppExports.R index 4430c6c65..98c0985f4 100644 --- a/R-proj/R/RcppExports.R +++ b/R-proj/R/RcppExports.R @@ -155,11 +155,11 @@ rounding <- function(P, random_walk = NULL, walk_length = NULL, parameters = NUL #' Sample points from a convex Polytope (H-polytope, V-polytope or a zonotope) or use direct methods for uniform sampling from the unit or the canonical or an arbitrary \eqn{d}-dimensional simplex and the boundary or the interior of a \eqn{d}-dimensional hypersphere #' -#' Sample N points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. +#' Sample n points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. #' The \eqn{d}-dimensional unit simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i\leq 1}, \eqn{x_i\geq 0}. The \eqn{d}-dimensional canonical simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i = 1}, \eqn{x_i\geq 0}. #' #' @param P A convex polytope. It is an object from class (a) Hpolytope or (b) Vpolytope or (c) Zonotope. -#' @param N The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}. +#' @param n The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}. #' @param distribution Optional. A string that declares the target distribution: a) \code{'uniform'} for the uniform distribution or b) \code{'gaussian'} for the multidimensional spherical distribution. The default target distribution is uniform. #' @param random_walk Optional. A string that declares the random walk method: a) \code{'CDHR'} for Coordinate Directions Hit-and-Run, b) \code{'RDHR'} for Random Directions Hit-and-Run, c) \code{'BaW'} for Ball Walk or d) \code{'BiW'} for Billiard walk. The default walk is \code{'BiW'} for the uniform distribution or \code{'CDHR'} for the Normal distribution. #' @param walk_length Optional. The number of the steps for the random walk. The default value is \eqn{1} for \code{'BiW'} and \eqn{\lfloor 10 + d/10\rfloor} otherwise, where \eqn{d} is the dimension that the polytope lies. @@ -182,7 +182,7 @@ rounding <- function(P, random_walk = NULL, walk_length = NULL, parameters = NUL #' @references \cite{Art B. Owen, #' \dQuote{Monte Carlo theory, methods and examples,} \emph{ Art Owen,} 2009.} #' -#' @return A \eqn{d\times N} matrix that contains, column-wise, the sampled points from the convex polytope P. +#' @return A \eqn{d\times n} matrix that contains, column-wise, the sampled points from the convex polytope P. #' @examples #' # uniform distribution from the 3d unit cube in V-representation using ball walk #' P = gen_cube(3, 'V') @@ -200,10 +200,10 @@ rounding <- function(P, random_walk = NULL, walk_length = NULL, parameters = NUL #' # 10000 uniform points from a 2-d arbitrary simplex #' V = matrix(c(2,3,-1,7,0,0),ncol = 2, nrow = 3, byrow = TRUE) #' P = Vpolytope$new(V) -#' points = sample_points(P, N = 10000, exact = TRUE) +#' points = sample_points(P, n = 10000, exact = TRUE) #' @export -sample_points <- function(P = NULL, N = NULL, distribution = NULL, random_walk = NULL, walk_length = NULL, exact = NULL, body = NULL, parameters = NULL, InnerPoint = NULL) { - .Call(`_volesti_sample_points`, P, N, distribution, random_walk, walk_length, exact, body, parameters, InnerPoint) +sample_points <- function(P = NULL, n = NULL, distribution = NULL, random_walk = NULL, walk_length = NULL, exact = NULL, body = NULL, parameters = NULL, InnerPoint = NULL) { + .Call(`_volesti_sample_points`, P, n, distribution, random_walk, walk_length, exact, body, parameters, InnerPoint) } #' The main function for volume approximation of a convex Polytope (H-polytope, V-polytope or a zonotope) diff --git a/R-proj/R/gen_cross.R b/R-proj/R/gen_cross.R index 6101f5ee1..05a65466b 100644 --- a/R-proj/R/gen_cross.R +++ b/R-proj/R/gen_cross.R @@ -3,7 +3,7 @@ #' This function can be used to generate the \eqn{d}-dimensional cross polytope in H- or V-representation. #' #' @param dimension The dimension of the cross polytope. -#' @param repr A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. +#' @param rep A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. #' #' @return A polytope class representing a cross polytope in H- or V-representation. #' @examples @@ -13,13 +13,13 @@ #' # generate a 15-dimension cross polytope in V-representation #' P = gen_cross(15, 'V') #' @export -gen_cross <- function(dimension, repr) { +gen_cross <- function(dimension, rep) { kind_gen = 2 m_gen = 0 - if (repr == "V") { + if (rep == "V") { Vpoly_gen = TRUE - } else if (repr == "H") { + } else if (rep == "H") { Vpoly_gen = FALSE } else { stop('Not a known representation.') diff --git a/R-proj/R/gen_cube.R b/R-proj/R/gen_cube.R index 5ecf1bcc0..d88647ff7 100644 --- a/R-proj/R/gen_cube.R +++ b/R-proj/R/gen_cube.R @@ -3,7 +3,7 @@ #' This function can be used to generate the \eqn{d}-dimensional unit hypercube \eqn{[-1,1]^d} in H- or V-representation. #' #' @param dimension The dimension of the hypercube -#' @param repr A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. +#' @param rep A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. #' #' @return A polytope class representing the unit \eqn{d}-dimensional hypercube in H- or V-representation. #' @examples @@ -13,13 +13,13 @@ #' # generate a 15-dimension hypercube in V-representation #' P = gen_cube(15, 'V') #' @export -gen_cube <- function(dimension, repr) { +gen_cube <- function(dimension, rep) { kind_gen = 1 m_gen = 0 - if (repr == "V") { + if (rep == "V") { Vpoly_gen = TRUE - } else if (repr == "H") { + } else if (rep == "H") { Vpoly_gen = FALSE } else { stop('Not a known representation.') diff --git a/R-proj/R/gen_rand_hpoly.R b/R-proj/R/gen_rand_hpoly.R index 9a5059119..2644529c5 100644 --- a/R-proj/R/gen_rand_hpoly.R +++ b/R-proj/R/gen_rand_hpoly.R @@ -3,19 +3,19 @@ #' This function can be used to generate a \eqn{d}-dimensional polytope in H-representation with \eqn{m} facets. We pick \eqn{m} random hyperplanes tangent on the \eqn{d}-dimensional unit hypersphere as facets. #' #' @param dimension The dimension of the convex polytope. -#' @param m The number of the facets. +#' @param nfacets The number of the facets. #' #' @return A polytope class representing a H-polytope. #' @examples #' # generate a 10-dimensional polytope with 50 facets #' P = gen_rand_hpoly(10, 50) #' @export -gen_rand_hpoly <- function(dimension, m) { +gen_rand_hpoly <- function(dimension, nfacets) { kind_gen = 6 Vpoly_gen = FALSE - Mat = poly_gen(kind_gen, Vpoly_gen, FALSE, dimension, m) + Mat = poly_gen(kind_gen, Vpoly_gen, FALSE, dimension, nfacets) # first column is the vector b b = Mat[,1] diff --git a/R-proj/R/gen_rand_vpoly.R b/R-proj/R/gen_rand_vpoly.R index 47001dbb5..9221a72cf 100644 --- a/R-proj/R/gen_rand_vpoly.R +++ b/R-proj/R/gen_rand_vpoly.R @@ -3,7 +3,7 @@ #' This function can be used to generate a \eqn{d}-dimensional polytope in V-representation with \eqn{m} vertices. We pick \eqn{m} random points from the boundary of the \eqn{d}-dimensional unit hypersphere as vertices. #' #' @param dimension The dimension of the convex polytope. -#' @param n_vertices The number of the vertices. +#' @param nvertices The number of the vertices. #' @param generator The body that the generator samples uniformly the vertices from: (a) 'cube' or (b) 'sphere'. #' #' @return A polytope class representing a V-polytope. @@ -11,7 +11,7 @@ #' # generate a 10-dimensional polytope defined as the convex hull of 25 random vertices #' P = gen_rand_vpoly(10, 25) #' @export -gen_rand_vpoly <- function(dimension, n_vertices, generator = NULL) { +gen_rand_vpoly <- function(dimension, nvertices, generator = NULL) { kind_gen = 4 @@ -23,7 +23,7 @@ gen_rand_vpoly <- function(dimension, n_vertices, generator = NULL) { } } - Mat = poly_gen(kind_gen, TRUE, FALSE, dimension, n_vertices) + Mat = poly_gen(kind_gen, TRUE, FALSE, dimension, nvertices) # first column is the vector b b = Mat[,1] diff --git a/R-proj/R/gen_rand_zonotope.R b/R-proj/R/gen_rand_zonotope.R index f35798be9..399ccdccf 100644 --- a/R-proj/R/gen_rand_zonotope.R +++ b/R-proj/R/gen_rand_zonotope.R @@ -3,7 +3,7 @@ #' This function can be used to generate a random \eqn{d}-dimensional zonotope defined by the Minkowski sum of \eqn{m} \eqn{d}-dimensional segments. We consider \eqn{m} random directions in \eqn{R^d} and for each direction we pick a random length in \eqn{[(,\sqrt{d}]} in order to define \eqn{m} segments. #' #' @param dimension The dimension of the zonotope. -#' @param n_segments The number of segments that generate the zonotope. +#' @param nsegments The number of segments that generate the zonotope. #' @param generator The distribution to pick the length of each segment from \eqn{[0,100]}: (a) 'uniform', (b) 'gaussian' or (c) 'exponential'. #' #' @return A polytope class representing a zonotope. @@ -12,7 +12,7 @@ #' # generate a 10-dimensional zonotope defined by the Minkowski sum of 20 segments #' P = gen_rand_zonotope(10, 20) #' @export -gen_rand_zonotope <- function(dimension, n_segments, generator = NULL) { +gen_rand_zonotope <- function(dimension, nsegments, generator = NULL) { kind_gen = 1 @@ -26,7 +26,7 @@ gen_rand_zonotope <- function(dimension, n_segments, generator = NULL) { } } - Mat = poly_gen(kind_gen, FALSE, TRUE, dimension, n_segments) + Mat = poly_gen(kind_gen, FALSE, TRUE, dimension, nsegments) # first column is the vector b b = Mat[,1] diff --git a/R-proj/R/gen_simplex.R b/R-proj/R/gen_simplex.R index 6d930cdd4..fc5b7a697 100644 --- a/R-proj/R/gen_simplex.R +++ b/R-proj/R/gen_simplex.R @@ -3,7 +3,7 @@ #' This function can be used to generate the \eqn{d}-dimensional unit simplex in H- or V-representation. #' #' @param dimension The dimension of the unit simplex. -#' @param repr A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. +#' @param rep A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation. #' #' @return A polytope class representing the \eqn{d}-dimensional unit simplex in H- or V-representation. #' @examples @@ -13,13 +13,13 @@ #' # generate a 20-dimensional simplex in V-representation #' P = gen_simplex(20, 'V') #' @export -gen_simplex <- function(dimension, repr) { +gen_simplex <- function(dimension, rep) { kind_gen = 3 m_gen = 0 - if (repr == "V") { + if (rep == "V") { Vpoly_gen = TRUE - } else if (repr == "H") { + } else if (rep == "H") { Vpoly_gen = FALSE } else { stop('Not a known representation.') diff --git a/R-proj/man/gen_cross.Rd b/R-proj/man/gen_cross.Rd index 4465330f2..040c09574 100644 --- a/R-proj/man/gen_cross.Rd +++ b/R-proj/man/gen_cross.Rd @@ -4,12 +4,12 @@ \alias{gen_cross} \title{Generator function for cross polytopes} \usage{ -gen_cross(dimension, repr) +gen_cross(dimension, rep) } \arguments{ \item{dimension}{The dimension of the cross polytope.} -\item{repr}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} +\item{rep}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} } \value{ A polytope class representing a cross polytope in H- or V-representation. diff --git a/R-proj/man/gen_cube.Rd b/R-proj/man/gen_cube.Rd index 5b5dd578b..108094125 100644 --- a/R-proj/man/gen_cube.Rd +++ b/R-proj/man/gen_cube.Rd @@ -4,12 +4,12 @@ \alias{gen_cube} \title{Generator function for hypercubes} \usage{ -gen_cube(dimension, repr) +gen_cube(dimension, rep) } \arguments{ \item{dimension}{The dimension of the hypercube} -\item{repr}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} +\item{rep}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} } \value{ A polytope class representing the unit \eqn{d}-dimensional hypercube in H- or V-representation. diff --git a/R-proj/man/gen_rand_hpoly.Rd b/R-proj/man/gen_rand_hpoly.Rd index 4b96999dc..0f72d562a 100644 --- a/R-proj/man/gen_rand_hpoly.Rd +++ b/R-proj/man/gen_rand_hpoly.Rd @@ -4,12 +4,12 @@ \alias{gen_rand_hpoly} \title{Generator function for random H-polytopes} \usage{ -gen_rand_hpoly(dimension, m) +gen_rand_hpoly(dimension, nfacets) } \arguments{ \item{dimension}{The dimension of the convex polytope.} -\item{m}{The number of the facets.} +\item{nfacets}{The number of the facets.} } \value{ A polytope class representing a H-polytope. diff --git a/R-proj/man/gen_rand_vpoly.Rd b/R-proj/man/gen_rand_vpoly.Rd index a994ce0ef..d57b56c33 100644 --- a/R-proj/man/gen_rand_vpoly.Rd +++ b/R-proj/man/gen_rand_vpoly.Rd @@ -4,12 +4,12 @@ \alias{gen_rand_vpoly} \title{Generator function for random V-polytopes} \usage{ -gen_rand_vpoly(dimension, n_vertices, generator = NULL) +gen_rand_vpoly(dimension, nvertices, generator = NULL) } \arguments{ \item{dimension}{The dimension of the convex polytope.} -\item{n_vertices}{The number of the vertices.} +\item{nvertices}{The number of the vertices.} \item{generator}{The body that the generator samples uniformly the vertices from: (a) 'cube' or (b) 'sphere'.} } diff --git a/R-proj/man/gen_rand_zonotope.Rd b/R-proj/man/gen_rand_zonotope.Rd index 8278490d4..dca32115b 100644 --- a/R-proj/man/gen_rand_zonotope.Rd +++ b/R-proj/man/gen_rand_zonotope.Rd @@ -4,12 +4,12 @@ \alias{gen_rand_zonotope} \title{Generator function for zonotopes} \usage{ -gen_rand_zonotope(dimension, n_segments, generator = NULL) +gen_rand_zonotope(dimension, nsegments, generator = NULL) } \arguments{ \item{dimension}{The dimension of the zonotope.} -\item{n_segments}{The number of segments that generate the zonotope.} +\item{nsegments}{The number of segments that generate the zonotope.} \item{generator}{The distribution to pick the length of each segment from \eqn{[0,100]}: (a) 'uniform', (b) 'gaussian' or (c) 'exponential'.} } diff --git a/R-proj/man/gen_simplex.Rd b/R-proj/man/gen_simplex.Rd index 90198543e..1da3ab1a5 100644 --- a/R-proj/man/gen_simplex.Rd +++ b/R-proj/man/gen_simplex.Rd @@ -4,12 +4,12 @@ \alias{gen_simplex} \title{Generator function for simplices} \usage{ -gen_simplex(dimension, repr) +gen_simplex(dimension, rep) } \arguments{ \item{dimension}{The dimension of the unit simplex.} -\item{repr}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} +\item{rep}{A string to declare the representation. It has to be \code{'H'} for H-representation or \code{'V'} for V-representation.} } \value{ A polytope class representing the \eqn{d}-dimensional unit simplex in H- or V-representation. diff --git a/R-proj/man/rounding.Rd b/R-proj/man/rounding.Rd index 959137787..10e5a6564 100644 --- a/R-proj/man/rounding.Rd +++ b/R-proj/man/rounding.Rd @@ -4,7 +4,8 @@ \alias{rounding} \title{Internal rcpp function for the rounding of a convex polytope} \usage{ -rounding(P, random_walk = NULL, walk_length = NULL, parameters = NULL) +rounding(P, random_walk = NULL, walk_length = NULL, + parameters = NULL) } \arguments{ \item{P}{A convex polytope (H- or V-representation or zonotope).} diff --git a/R-proj/man/sample_points.Rd b/R-proj/man/sample_points.Rd index ca8f08d21..3d18a43a9 100644 --- a/R-proj/man/sample_points.Rd +++ b/R-proj/man/sample_points.Rd @@ -4,14 +4,14 @@ \alias{sample_points} \title{Sample points from a convex Polytope (H-polytope, V-polytope or a zonotope) or use direct methods for uniform sampling from the unit or the canonical or an arbitrary \eqn{d}-dimensional simplex and the boundary or the interior of a \eqn{d}-dimensional hypersphere} \usage{ -sample_points(P = NULL, N = NULL, distribution = NULL, - random_walk = NULL, walk_length = NULL, exact = NULL, body = NULL, - parameters = NULL, InnerPoint = NULL) +sample_points(P = NULL, n = NULL, distribution = NULL, + random_walk = NULL, walk_length = NULL, exact = NULL, + body = NULL, parameters = NULL, InnerPoint = NULL) } \arguments{ \item{P}{A convex polytope. It is an object from class (a) Hpolytope or (b) Vpolytope or (c) Zonotope.} -\item{N}{The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}.} +\item{n}{The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}.} \item{distribution}{Optional. A string that declares the target distribution: a) \code{'uniform'} for the uniform distribution or b) \code{'gaussian'} for the multidimensional spherical distribution. The default target distribution is uniform.} @@ -35,10 +35,10 @@ sample_points(P = NULL, N = NULL, distribution = NULL, \item{InnerPoint}{A \eqn{d}-dimensional numerical vector that defines a point in the interior of polytope P.} } \value{ -A \eqn{d\times N} matrix that contains, column-wise, the sampled points from the convex polytope P. +A \eqn{d\times n} matrix that contains, column-wise, the sampled points from the convex polytope P. } \description{ -Sample N points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. +Sample n points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. The \eqn{d}-dimensional unit simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i\leq 1}, \eqn{x_i\geq 0}. The \eqn{d}-dimensional canonical simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i = 1}, \eqn{x_i\geq 0}. } \examples{ @@ -58,7 +58,7 @@ points = sample_points(exact = TRUE, body = "hypersphere", parameters = list("di # 10000 uniform points from a 2-d arbitrary simplex V = matrix(c(2,3,-1,7,0,0),ncol = 2, nrow = 3, byrow = TRUE) P = Vpolytope$new(V) -points = sample_points(P, N = 10000, exact = TRUE) +points = sample_points(P, n = 10000, exact = TRUE) } \references{ \cite{R.Y. Rubinstein and B. Melamed, diff --git a/R-proj/man/volume.Rd b/R-proj/man/volume.Rd index 9414d5a94..f1f2b7eac 100644 --- a/R-proj/man/volume.Rd +++ b/R-proj/man/volume.Rd @@ -5,7 +5,8 @@ \title{The main function for volume approximation of a convex Polytope (H-polytope, V-polytope or a zonotope)} \usage{ volume(P, walk_length = NULL, error = NULL, inner_ball = NULL, - algo = NULL, random_walk = NULL, rounding = NULL, parameters = NULL) + algo = NULL, random_walk = NULL, rounding = NULL, + parameters = NULL) } \arguments{ \item{P}{A convex polytope. It is an object from class (a) Hpolytope or (b) Vpolytope or (c) Zonotope.} diff --git a/R-proj/man/zonotope_approximation.Rd b/R-proj/man/zonotope_approximation.Rd index 81f8c1659..40263c74b 100644 --- a/R-proj/man/zonotope_approximation.Rd +++ b/R-proj/man/zonotope_approximation.Rd @@ -5,8 +5,8 @@ \title{A function to over-approximate a zonotope with PCA method and to evaluate the approximation by computing a ratio of fitness.} \usage{ zonotope_approximation(Z, fit_ratio = NULL, walk_length = NULL, - error = NULL, inner_ball = NULL, random_walk = NULL, rounding = NULL, - parameters = NULL) + error = NULL, inner_ball = NULL, random_walk = NULL, + rounding = NULL, parameters = NULL) } \arguments{ \item{Z}{A zonotope.} diff --git a/R-proj/src/sample_points.cpp b/R-proj/src/sample_points.cpp index 94555caf3..5ed69aae7 100644 --- a/R-proj/src/sample_points.cpp +++ b/R-proj/src/sample_points.cpp @@ -28,11 +28,11 @@ //' Sample points from a convex Polytope (H-polytope, V-polytope or a zonotope) or use direct methods for uniform sampling from the unit or the canonical or an arbitrary \eqn{d}-dimensional simplex and the boundary or the interior of a \eqn{d}-dimensional hypersphere //' -//' Sample N points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. +//' Sample n points with uniform or multidimensional spherical gaussian -centered in an internal point- target distribution. //' The \eqn{d}-dimensional unit simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i\leq 1}, \eqn{x_i\geq 0}. The \eqn{d}-dimensional canonical simplex is the set of points \eqn{\vec{x}\in \R^d}, s.t.: \eqn{\sum_i x_i = 1}, \eqn{x_i\geq 0}. //' //' @param P A convex polytope. It is an object from class (a) Hpolytope or (b) Vpolytope or (c) Zonotope. -//' @param N The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}. +//' @param n The number of points that the function is going to sample from the convex polytope. The default value is \eqn{100}. //' @param distribution Optional. A string that declares the target distribution: a) \code{'uniform'} for the uniform distribution or b) \code{'gaussian'} for the multidimensional spherical distribution. The default target distribution is uniform. //' @param random_walk Optional. A string that declares the random walk method: a) \code{'CDHR'} for Coordinate Directions Hit-and-Run, b) \code{'RDHR'} for Random Directions Hit-and-Run, c) \code{'BaW'} for Ball Walk or d) \code{'BiW'} for Billiard walk. The default walk is \code{'BiW'} for the uniform distribution or \code{'CDHR'} for the Normal distribution. //' @param walk_length Optional. The number of the steps for the random walk. The default value is \eqn{1} for \code{'BiW'} and \eqn{\lfloor 10 + d/10\rfloor} otherwise, where \eqn{d} is the dimension that the polytope lies. @@ -55,7 +55,7 @@ //' @references \cite{Art B. Owen, //' \dQuote{Monte Carlo theory, methods and examples,} \emph{ Art Owen,} 2009.} //' -//' @return A \eqn{d\times N} matrix that contains, column-wise, the sampled points from the convex polytope P. +//' @return A \eqn{d\times n} matrix that contains, column-wise, the sampled points from the convex polytope P. //' @examples //' # uniform distribution from the 3d unit cube in V-representation using ball walk //' P = gen_cube(3, 'V') @@ -73,11 +73,11 @@ //' # 10000 uniform points from a 2-d arbitrary simplex //' V = matrix(c(2,3,-1,7,0,0),ncol = 2, nrow = 3, byrow = TRUE) //' P = Vpolytope$new(V) -//' points = sample_points(P, N = 10000, exact = TRUE) +//' points = sample_points(P, n = 10000, exact = TRUE) //' @export // [[Rcpp::export]] Rcpp::NumericMatrix sample_points(Rcpp::Nullable P = R_NilValue, - Rcpp::Nullable N = R_NilValue, + Rcpp::Nullable n = R_NilValue, Rcpp::Nullable distribution = R_NilValue, Rcpp::Nullable random_walk = R_NilValue, Rcpp::Nullable walk_length = R_NilValue, @@ -108,7 +108,7 @@ Rcpp::NumericMatrix sample_points(Rcpp::Nullable P = R_NilValue std::list randPoints; std::pair InnerBall; - numpoints = (!N.isNotNull()) ? 100 : Rcpp::as(N); + numpoints = (!n.isNotNull()) ? 100 : Rcpp::as(n); if (exact.isNotNull()) { if (P.isNotNull()) { diff --git a/R-proj/src/volume.cpp b/R-proj/src/volume.cpp index b7c6eefc4..2414f0e6e 100644 --- a/R-proj/src/volume.cpp +++ b/R-proj/src/volume.cpp @@ -279,6 +279,10 @@ double volume (Rcpp::Reference P, Rcpp::Nullable walk_length = R_ throw Rcpp::exception("Unknown walk type!"); } + if (e <= 0.0) { + throw Rcpp::exception("The error parameter has to be a positive number!"); + } + if (!rounding.isNotNull() && type == 2){ round = true; } else { diff --git a/test/CMakeLists.txt b/test/CMakeLists.txt index 50c8e0eca..8478bf30e 100644 --- a/test/CMakeLists.txt +++ b/test/CMakeLists.txt @@ -69,12 +69,12 @@ else () add_executable (volume_test volume_test.cpp $) add_executable (cheb_test chebychev_test.cpp $) #add_executable (rounding_test rounding_test.cpp $) - add_executable (volumeCV_test volumeCV_test.cpp $) - add_executable (VpolyCV_test VpolyCV_test.cpp $) + add_executable (volumeCG_test volumeCG_test.cpp $) + add_executable (VpolyCG_test VpolyCG_test.cpp $) add_executable (VpolyVol_test VpolyVol_test.cpp $) add_executable (ZonotopeVol_test ZonotopeVol_test.cpp $) add_executable (cool_bodies_bill_test cooling_bodies_bill_test.cpp $) - #add_executable (ZonotopeVolCV_test ZonotopeVolCV_test.cpp $) + #add_executable (ZonotopeVolCG_test ZonotopeVolCG_test.cpp $) add_test(NAME volume_cube COMMAND volume_test -tc=cube) add_test(NAME volume_cross COMMAND volume_test -tc=cross) @@ -83,15 +83,15 @@ else () add_test(NAME volume_simplex COMMAND volume_test -tc=simplex) add_test(NAME volume_skinny_cube COMMAND volume_test -tc=skinny_cube) - add_test(NAME volumeCV_cube COMMAND volumeCV_test -tc=cube) - add_test(NAME volumeCV_cross COMMAND volumeCV_test -tc=cross) - add_test(NAME volumeCV_birkhoff COMMAND volumeCV_test -tc=birk) - add_test(NAME volumeCV_prod_simplex COMMAND volumeCV_test -tc=prod_simplex) - #add_test(NAME volumeCV_simplex COMMAND volumeCV_test -tc=simplex) + add_test(NAME volumeCG_cube COMMAND volumeCG_test -tc=cube) + add_test(NAME volumeCG_cross COMMAND volumeCG_test -tc=cross) + add_test(NAME volumeCG_birkhoff COMMAND volumeCG_test -tc=birk) + add_test(NAME volumeCG_prod_simplex COMMAND volumeCG_test -tc=prod_simplex) + add_test(NAME volumeCG_simplex COMMAND volumeCG_test -tc=simplex) - #add_test(NAME VpolyCV_cube COMMAND VpolyCV_test -tc=cube) - add_test(NAME VpolyCV_cross COMMAND VpolyCV_test -tc=cross) - add_test(NAME VpolyCV_simplex COMMAND VpolyCV_test -tc=simplex) + #add_test(NAME VpolyCG_cube COMMAND VpolyCG_test -tc=cube) + add_test(NAME VpolyCG_cross COMMAND VpolyCG_test -tc=cross) + add_test(NAME VpolyCG_simplex COMMAND VpolyCG_test -tc=simplex) add_test(NAME VpolyVol_cube COMMAND VpolyVol_test -tc=cube) add_test(NAME VpolyVol_cross COMMAND VpolyVol_test -tc=cross) @@ -99,8 +99,8 @@ else () add_test(NAME ZonotopeVol4 COMMAND ZonotopeVol_test -tc=4_dimensional) - #add_test(NAME ZonotopeVolCV4 COMMAND ZonotopeVolCV_test -tc=4_dimensional) - #add_test(NAME ZonotopeVolCV5 COMMAND ZonotopeVolCV_test -tc=5_dimensional) + #add_test(NAME ZonotopeVolCG4 COMMAND ZonotopeVolCG_test -tc=4_dimensional) + #add_test(NAME ZonotopeVolCG5 COMMAND ZonotopeVolCG_test -tc=5_dimensional) add_test(NAME cheb_cube COMMAND cheb_test -tc=cheb_cube) add_test(NAME cheb_cross COMMAND cheb_test -tc=cheb_cross) @@ -112,7 +112,7 @@ else () add_test(NAME cool_bodies_cube COMMAND cool_bodies_bill_test -tc=cube) add_test(NAME cool_bodies_cross COMMAND cool_bodies_bill_test -tc=cross) add_test(NAME cool_bodies_birkhoff COMMAND cool_bodies_bill_test -tc=birk) - #add_test(NAME cool_bodies_prod_simplex COMMAND cool_bodies_bill_test -tc=prod_simplex) + add_test(NAME cool_bodies_prod_simplex COMMAND cool_bodies_bill_test -tc=prod_simplex) add_test(NAME cool_bodies_simplex COMMAND cool_bodies_bill_test -tc=simplex) add_test(NAME cool_bodies_skinny_cube COMMAND cool_bodies_bill_test -tc=skinny_cube) @@ -125,12 +125,12 @@ else () TARGET_LINK_LIBRARIES(volume_test ${LP_SOLVE}) TARGET_LINK_LIBRARIES(cheb_test ${LP_SOLVE}) #TARGET_LINK_LIBRARIES(rounding_test ${LP_SOLVE}) - TARGET_LINK_LIBRARIES(volumeCV_test ${LP_SOLVE}) - TARGET_LINK_LIBRARIES(VpolyCV_test ${LP_SOLVE}) + TARGET_LINK_LIBRARIES(volumeCG_test ${LP_SOLVE}) + TARGET_LINK_LIBRARIES(VpolyCG_test ${LP_SOLVE}) TARGET_LINK_LIBRARIES(VpolyVol_test ${LP_SOLVE}) TARGET_LINK_LIBRARIES(ZonotopeVol_test ${LP_SOLVE}) TARGET_LINK_LIBRARIES(cool_bodies_bill_test ${LP_SOLVE}) - #TARGET_LINK_LIBRARIES(ZonotopeVolCV_test ${LP_SOLVE}) + #TARGET_LINK_LIBRARIES(ZonotopeVolCG_test ${LP_SOLVE}) endif() diff --git a/test/VpolyCV_test.cpp b/test/VpolyCG_test.cpp similarity index 100% rename from test/VpolyCV_test.cpp rename to test/VpolyCG_test.cpp diff --git a/test/ZonotopeVolCV_test.cpp b/test/ZonotopeVolCG_test.cpp similarity index 100% rename from test/ZonotopeVolCV_test.cpp rename to test/ZonotopeVolCG_test.cpp diff --git a/test/cooling_bodies_bill_test.cpp b/test/cooling_bodies_bill_test.cpp index fef5faffe..895dec6e1 100644 --- a/test/cooling_bodies_bill_test.cpp +++ b/test/cooling_bodies_bill_test.cpp @@ -46,7 +46,7 @@ void test_cool_bodies(Polytope &HP, NT expected, NT tolerance=0.1, bool round = // Setup the parameters int n = HP.dimension(); - int walk_len=1; + int walk_len=3; int nexp=1, n_threads=1; NT e=0.1, err=0.0000000001, diameter = diam, round_val = 1.0; int rnum = std::pow(e,-2) * 400 * n * std::log(n); @@ -76,7 +76,7 @@ void test_cool_bodies(Polytope &HP, NT expected, NT tolerance=0.1, bool round = urdist,urdist1,-1.0,false,false,false,false,false,false,false,false,true); NT lb = 0.1, ub = 0.15, p = 0.75, rmax = 0.0, alpha = 0.2; - int W = 250, NNu = 140, nu =10; + int W = 500, NNu = 150, nu =10; bool win2 = false; vars_ban var_ban(lb, ub, p, rmax, alpha, W, NNu, nu, win2); @@ -193,9 +193,9 @@ void call_test_prod_simplex() { //P = gen_prod_simplex(15); //test_volume(P, std::pow(1.0 / factorial(15.0), 2)); - std::cout << "--- Testing volume of H-prod_simplex20" << std::endl; - P = gen_prod_simplex(20); - test_cool_bodies(P, std::pow(1.0 / factorial(20.0), 2.0), 0.2, true); + //std::cout << "--- Testing volume of H-prod_simplex20" << std::endl; + //P = gen_prod_simplex(20); + //test_cool_bodies(P, std::pow(1.0 / factorial(20.0), 2.0), 0.2, true); } template @@ -208,15 +208,15 @@ void call_test_simplex() { std::cout << "--- Testing volume of H-simplex10" << std::endl; P = gen_simplex(10, false); - test_cool_bodies(P, 1.0 / factorial(10.0), 0.1, false, 1.5); + test_cool_bodies(P, 1.0 / factorial(10.0), 0.2, false, 2.0); std::cout << "--- Testing volume of H-simplex20" << std::endl; P = gen_simplex(20, false); - test_cool_bodies(P, 1.0 / factorial(20.0), 0.1, false, 1.5); + test_cool_bodies(P, 1.0 / factorial(20.0), 0.2, false, 2.0); std::cout << "--- Testing volume of H-simplex30" << std::endl; P = gen_simplex(30, false); - test_cool_bodies(P, 1.0 / factorial(30.0), 0.1, false, 1.5); + test_cool_bodies(P, 1.0 / factorial(30.0), 0.2, false, 2.0); //std::cout << "--- Testing volume of H-simplex40" << std::endl; //P = gen_simplex(40, false); diff --git a/test/vol.cpp b/test/vol.cpp index 728b87eae..22cb62ac3 100644 --- a/test/vol.cpp +++ b/test/vol.cpp @@ -446,6 +446,11 @@ int main(const int argc, const char** argv) } } + if ( e*error <= 0.0) { + std::cout << "The error parameter has to be a positive number!\n" << std::endl; + exit(-1); + } + if (!user_randwalk) { if (Zono || Vpoly) { if (CB) { diff --git a/test/volumeCV_test.cpp b/test/volumeCG_test.cpp similarity index 99% rename from test/volumeCV_test.cpp rename to test/volumeCG_test.cpp index 9897559b6..05eae1572 100644 --- a/test/volumeCV_test.cpp +++ b/test/volumeCG_test.cpp @@ -33,13 +33,13 @@ void test_CV_volume(Polytope &HP, NT expected, NT tolerance=0.3) // Setup the parameters int n = HP.dimension(); - int walk_len=1; + int walk_len=3; int nexp=1, n_threads=1; NT e=0.1, err=0.0000000001; NT C=2.0,ratio,frac=0.1,delta=-1.0; int rnum = std::pow(e,-2) * 400 * n * std::log(n); int N = 500 * ((int) C) + ((int) (n * n / 2)); - int W = 4*n*n+500; + int W = 6*n*n+800; ratio = 1.0-1.0/(NT(n)); unsigned seed = std::chrono::system_clock::now().time_since_epoch().count(); RNGType rng(seed);