Skip to content

Commit

Permalink
Major refactoring - new API for genthat and decorator
Browse files Browse the repository at this point in the history
Closes #165, #149, #148, #140, #139, #121, #118, #112
  • Loading branch information
fikovnik committed Jul 3, 2018
1 parent 1ccc72d commit 3e9bb4e
Show file tree
Hide file tree
Showing 51 changed files with 1,574 additions and 1,455 deletions.
6 changes: 3 additions & 3 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ export(capture)
export(compute_coverage)
export(compute_tests_coverage)
export(copy_traces)
export(create_decorator)
export(create_sequence_tracer)
export(create_set_tracer)
export(create_tracer)
Expand All @@ -36,18 +35,19 @@ export(gen_from_package)
export(gen_from_source)
export(generate_test)
export(generate_test_file)
export(get_decorator)
export(get_decorations)
export(get_package_version)
export(get_tracer)
export(is_debug_enabled)
export(is_decorated)
export(is_tracing_enabled)
export(process_traces)
export(record_trace)
export(reset_function)
export(reset_functions)
export(reset_traces)
export(run_generated_test)
export(save_test)
export(set_decorator)
export(set_tracer)
export(store_trace)
export(test_generated_file)
Expand Down
4 changes: 4 additions & 0 deletions R/RcppExports.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,3 +53,7 @@ environment_name_as_code <- function(env) {
.Call('_genthat_environment_name_as_code', PACKAGE = 'genthat', env)
}

sexp_address <- function(s) {
.Call('_genthat_sexp_address', PACKAGE = 'genthat', s)
}

35 changes: 23 additions & 12 deletions R/capture.R
Original file line number Diff line number Diff line change
@@ -1,7 +1,14 @@
# Default function entry decorator.
# Creates the trace record and stores it into the trace vector.
record_trace <- function(name, pkg=NULL, args, retv, error, seed,
env=parent.frame(), tracer=get_tracer()) {
#' @export
record_trace <- function(info) {

name <- info$name
package <- info$package
args <- info$args
retv <- info$retv
error <- info$error
seed <- info$seed
env <- if (is.null(info$env)) parent.frame() else info$env
tracer <- if (is.null(info$tracer)) get_tracer() else info$tracer

# TODO: (performance) all this makes sense only if there are symbols anywhere in args
# get callee globals (free variables) that we need to capture
Expand Down Expand Up @@ -33,6 +40,7 @@ record_trace <- function(name, pkg=NULL, args, retv, error, seed,
# in the parent frame
tmp_name <- names(args)[[1]]
value_name <- names(args)[[length(args)]]
# TODO: this should be just -1
call_env <- sys.frame(sys.nframe() - 1)

# we are trying to get the *tmp*
Expand All @@ -53,11 +61,11 @@ record_trace <- function(name, pkg=NULL, args, retv, error, seed,
globals <- as.list(environment(extract_closure(callee)), all.names=TRUE)
globals <- lapply(globals, duplicate_global_var)

create_trace(name, pkg, args=args, globals=globals, retv=retv, seed=seed, error=error)
create_trace(name, package, args=args, globals=globals, retv=retv, seed=seed, error=error)
}, error=function(e) {
create_trace(name, pkg, args=args, failure=e)
create_trace(name, package, args=args, failure=e)
}, warning=function(e) {
create_trace(name, pkg, args=args, failure=e)
create_trace(name, package, args=args, failure=e)
})

store_trace(tracer, trace)
Expand Down Expand Up @@ -182,17 +190,17 @@ get_symbol_values <- function(names, env=parent.frame(), include_base_symbols=FA
}

get_variable_value_or_reference <- function(name, env) {
pkg <- get_package_name(env)
package <- get_package_name(env)

if (is_base_env(env)) {
substitute(NAME, list(NAME=as.name(name)))
} else if (is_package_environment(env)) {
substitute(PKG::NAME, list(PKG=as.name(pkg), NAME=as.name(name)))
substitute(PACKAGE::NAME, list(PACKAGE=as.name(package), NAME=as.name(name)))
} else if (is_package_namespace(env)) {
if (name %in% getNamespaceExports(env)) {
substitute(PKG::NAME, list(PKG=as.name(pkg), NAME=as.name(name)))
substitute(PACKAGE::NAME, list(PACKAGE=as.name(package), NAME=as.name(name)))
} else {
substitute(PKG:::NAME, list(PKG=as.name(pkg), NAME=as.name(name)))
substitute(PACKAGE:::NAME, list(PACKAGE=as.name(package), NAME=as.name(name)))
}
} else {
get(name, envir=env, inherits=FALSE)
Expand Down Expand Up @@ -276,7 +284,10 @@ extract_closure <- function(fun, name=substitute(fun), .visited=list()) {
# we should only link the environments in the case it is necessary
# i.e. any of the global functions need access to this environment
# the idea is demonstrated in the test-capture.R
link_environments(e, .fun_filter=function(x) is.local_closure(x) && isTRUE(attr(x, "genthat_needs_link")))
link_environments(e, .fun_filter=function(x) {
is.local_closure(x) && isTRUE(attr(x, "genthat_needs_link"))
})

e
}

Expand Down
181 changes: 181 additions & 0 deletions R/create-decorated-function.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,181 @@
create_decorated_function <- function(fun, name, package,
onentry=NULL, onexit=NULL, onerror=NULL) {

stopifnot(is.function(fun))
stopifnot(is_chr_scalar(name))
stopifnot(is.null(package) || is_chr_scalar(package))
stopifnot(is.null(onentry) || is.function(onentry))
stopifnot(is.null(onexit) || is.function(onexit))
stopifnot(is.null(onerror) || is.function(onerror))
stopifnot(!all(is.null(onentry), is.null(onexit), is.null(onerror)))

prologue <- if (!is.null(onentry)) {
substitute(
ONENTRY(
list(
name=NAME,
package=PACKAGE,
seed=`__genthat_captured_seed`,
env=parent.frame(),
decorator="onentry"
)
),
list(ONENTRY=onentry, NAME=name, PACKAGE=package)
)
} else {
NULL
}

onexit_call <- if (!is.null(onexit)) {
substitute(
ONEXIT(
list(
name=NAME,
package=PACKAGE,
seed=`__genthat_captured_seed`,
env=parent.frame(),
args=args,
retv=retv,
decorator="onexit"
)
),
list(ONEXIT=onexit, NAME=name, PACKAGE=package)
)
} else {
NULL
}

onerror_call <- if (!is.null(onerror)) {
substitute(
ONERROR(
list(
name=NAME,
package=PACKAGE,
seed=`__genthat_captured_seed`,
env=parent.frame(),
args=args,
message=geterrmessage(),
decorator="onerror"
)
),
list(ONERROR=onerror, NAME=name, PACKAGE=package)
)
} else {
NULL
}

epilogue <- if (!is.null(onexit_call) || !is.null(onerror_call)) {

expr <- if (!is.null(onexit_call) && !is.null(onerror_call)) {
substitute(
if (!identical(retv, default)) {
onexit_call
} else {
onerror_call
}
)
} else if (!is.null(onexit_call)) {
substitute(
if (!identical(retv, default)) {
onexit_call
}
)
} else {
substitute(
if (identical(retv, default)) {
onerror_call
}
)
}

substitute(
on.exit({
if (.Internal(getOption("genthat.tracing"))) {
.Internal(options(genthat.tracing=FALSE))

default <- genthat:::.genthat_default_retv
retv <- returnValue(default=default)
args <- as.list(match.call())[-1]

expr

.Internal(options(genthat.tracing=TRUE))
}
})
)
} else {
NULL
}

# this one will capture the first argument passed to `fun<-`
genthat_tmp <- if (endsWith(name, "<-")) {
substitute(`__genthat_tmp` <- ARG_NAME, list(ARG_NAME=as.name(names(formals(fun))[1])))
} else {
NULL
}

obody <- body(fun)

# the epilogue is above the body since it will be run in the on.exit handler
nbody <- if (!is.null(prologue) && !is.null(epilogue)) {
if (is.null(genthat_tmp)) {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())

prologue
epilogue
obody
})
} else {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())
genthat_tmp

prologue
epilogue
obody
})
}
} else if (!is.null(prologue)) {
if (is.null(genthat_tmp)) {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())

prologue
obody
})
} else {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())
genthat_tmp

prologue
obody
})
}
} else if (!is.null(epilogue)) {
if (is.null(genthat_tmp)) {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())
genthat_tmp

epilogue
obody
})
} else {
substitute({
`__genthat_captured_seed` <- get(".Random.seed", envir=globalenv())
genthat_tmp

epilogue
obody
})
}
} else {
stop("Not possible")
}

# we do not copy attributes since we are only interested in
# the body of the function
create_function(params=formals(fun), body=nbody, env=environment(fun))
}
Loading

0 comments on commit 3e9bb4e

Please sign in to comment.