[Rd] Extending suggestion for stopifnot

ivo welch ivo.welch at gmail.com
Wed Aug 21 00:00:18 CEST 2013


thx, deepayan:  how is stopifnot better than
    if (!all(...)) stop()
given that we have stopifnot() and I have seen it used often, I think
my two suggestions would make it better.

thx, michael:  the %and% and %or% constructs are indeed relics of my
perl background.  my own definition is

`%and%` <- function(e1, e2) {  if (e1) { if (is.character(e2))
abort.estring(e2) else eval(e2) } }

it's syntactic sugar.  my abort.estring() function prints the
character as n estring() [extended string, see below] and exits.  it
can probably be written a lot better.  remember, I am not an expert.

thx, peter: the estring has the advantage of having it all in one
string, which allows me to say, e.g.,
   (x) %or% "x is not true but {{x}}"
the comma here does not work.  it basically becomes an interpolated
string, just like the construct "x is $x" in perl.

thx, bill: ensureThat() is not a base R function.  uggh---I think you
are right on precedence.  I always use parens around my conditions.
old C habit from decades ago, so I never ran into this problem.  if()
is good enough.  my main suggestion was adding an optional message at
the end of stopifnot(), and possibly extended (interpolated) strings.

thx, brian:  I think of lambda.r as being more "heavyweight" and
requiring a modestly steeper learning curve.  if it was standard in
base R, I would definitely switch to it.  I think we want a system
that my students are taught to use from day 1.


in sum, I agree that one accomplish the functionality in base R.  my
initial suggestion was very simple and small: (1) adding an optional
character string at the end of an existing function, stopifnot().  (2)
I think "estrings" (that behave like characters but are interpolated
before printout) are useful in the same way perl interpolated strings
are useful.  this would be a bigger change.  some people would like
it.  others don't see the advantage.  I think the benefits would
outweigh the costs.  (3) I just mentioned %and% and %or% as an
"aside".  it this is definitely a bigger change, where we can all
agree to disagree whether we like this in code or not.  just ignore
#3.

best,

/iaw


estring <- function(e2, N.UP =2) {

  rx <- "(?<=\\{\\{).*?(?=\\}\\})"

  match <- gregexpr(rx, e2, perl=TRUE)

  syntax <- regmatches(e2, match)[[1]]
  syntax <- lapply(syntax, parse, file="", n=NULL)
##  syntax<-lapply(syntax, eval.parent, n=N.UP)
  r <- tryCatch( syntax<-lapply(syntax, eval.parent, n=N.UP), error=
function(e) NULL )
  if (is.null(r)) r <- tryCatch( syntax<-lapply(syntax, eval.parent,
n=N.UP+1), error= function(e) NULL )
  if (is.null(r)) r <- tryCatch( syntax<-lapply(syntax, eval.parent,
n=N.UP-1), error= function(e) NULL )
  if (is.null(r)) r <- tryCatch( syntax<-lapply(syntax, eval.parent,
n=N.UP-2), error= function(e) "unknown variable" )
  ## the return is now ignored.  if we cannot recognize the syntax, we
just leave it.

  s<- unlist(sys.calls())
  if (length(s)>1) cat("Function '",
as.character(s[[length(s)-N.UP+1]]), "':\n\t", sep="") else
cat("[GlobalEnv]:\t")
  regmatches(e2, match) <- "%s"

  do.call(sprintf, c(fmt=e2, '...'=syntax) )
}
----
Ivo Welch (ivo.welch at gmail.com)
http://www.ivo-welch.info/
J. Fred Weston Professor of Finance
Anderson School at UCLA, C519
Director, UCLA Anderson Fink Center for Finance and Investments
Free Finance Textbook, http://book.ivo-welch.info/
Editor, Critical Finance Review, http://www.critical-finance-review.org/



On Tue, Aug 20, 2013 at 2:14 PM, Brian Rowe <rowe at muxspace.com> wrote:
> If all you care about is emulating static type checking, then you can also accomplish the same thing with lambda.r using type constraints on function definitions.
>
> e.g.
>> f(m) %::% matrix : matrix
>> f(m) %as% { m }
>
>> f(as.data.frame(matrix(rnorm(12),nrow=3)))
> Error in UseFunction("f", ...) : No valid function for 'f(data.frame)'
>
>> f(1)
> Error in UseFunction("f", ...) : No valid function for 'f(1)'
>
>> f
> <function>
> [[1]]
> f(m) %::% matrix:matrix
> f(m) %as% …
>
>
>
> On Aug 20, 2013, at 4:36 PM, Peter Langfelder <peter.langfelder at gmail.com> wrote:
>
>> On Tue, Aug 20, 2013 at 11:41 AM, ivo welch <ivo.welch at anderson.ucla.edu> wrote:
>>> I am using a variant of stopifnot a lot.  can I suggest that base R
>>> extends its functionality?  I know how to do this for myself.  this is
>>> a suggestion for beginners and students.  I don't think it would break
>>> anything.
>>>
>>> first, I think it would be more useful if it had an optional character
>>> string, so users could write
>>>
>>>  stopifnot( is.matrix(m), "m is not a matrix" )
>>>
>>> this would mean that stopifnot would have to detect whether the last
>>> argument is a string.  (I think stopifnot should have had only one
>>> condition, and one should have used all() to test multiple conditions,
>>> but this is a bridge that was already crossed.)  upon failure,
>>> stopifnot should print the character string.  that's it.
>>>
>>>
>>> A second enhancement would be a "smart string", which knows that
>>> everything inside {{...}} should be evaluated.
>>>
>>>  stopifnot( is.matrix(m), "m is not a matrix, but a {{class(m)}}" )
>>
>> I think using a function (in this case paste) is cleaner:
>>
>> paste("m is not a matrix, but a", class(m))
>>
>> It avoids adding a new convention ("evaluate everything between {{
>> }}") and has additional arguments.
>>
>>>
>>>
>>> my own programming variant looks even nicer,
>>>
>>>   is.matrix(m) %or% "m is not a matrix but a {{class(m)}}"
>>
>> In R you can write it as
>>
>> is.matrix(m) || stop("m is not a matrix but a ", class(m))
>>
>> Examples:
>>
>> m = 1
>>> is.matrix(m) || stop("m is not a matrix but a ", class(m))
>> Error: m is not a matrix but a numeric
>>
>>> m = matrix(0,2,2)
>>> is.matrix(m) || stop("m is not a matrix but a ", class(m))
>> [1] TRUE
>>
>> But the construct
>>
>> if (!is.matrix(m)) stop("m is not a matrix but a ", class(m))
>>
>> is more readable for people not used to Pearl.
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>



More information about the R-devel mailing list