I've read in many places that R semantics are based on Scheme semantics. As a long-time Lisp user and implementor, I've tried to make this more precise, and this is what I've found so far. I've excluded trivial things that aren't basic semantic issues: support for arbitrary-precision integers; subscripting; general style; etc. I would appreciate corrections or additions from more experienced users of R -- I'm sure that some of the points below simply reflect my ignorance. ==Similarities to Scheme= R has first-class function closures. (i.e. correctly supports upward and downward funarg). R has a single namespace for functions and variables (Lisp-1). ==Important dissimilarities to Scheme (as opposed to other Lisps)= R is not properly tail-recursive. R does not have continuations or call-with-current-continuation or other mechanisms for implementing coroutines, general iterators, and the like. R supports keyword arguments. ==Similarities to Lisp and other dynamic languages, including Scheme= R is runtime-typed and garbage-collected. R supports nested read-eval-print loops for debugging etc. R expressions are represented as user-manipulable data structures. ==Dissimilarities to all (modern) Lisps, including Scheme= R has call-by-need, not call-by-object-value. R does not have macros. R objects are values, not pointers, so a<-1:10; b<-a; b[1]<-999; a[1] => 999. Similarly, functions cannot modify the contents of their arguments. There is no equivalent to set-car!/rplaca (not even pairlists and expressions). For example, r<-pairlist(1,2); r[[1]]<-r does not create a circular list. And in general there doesn't seem to be substructure sharing at the semantic level (though there may be in the implementation). R does not have multiple value return in the Lisp sense. R assignment creates a new local variable on first assignment, dynamically. So static analysis is not enough to determine variable reference (R is not referentially transparent). Example: ff <- function(a){if (a) x<-1; x} ; x<-99; ff(T) -> 1; ff(F) -> 99. In R, most data types (including numeric vectors) do not have a standard external representation which can be read back in without evaluation. R coerces logicals to numbers and numbers to strings. Lisps are stricter about automatic type conversion -- except that false a.k.a. NIL == () in Lisps other than Scheme. [[alternative HTML version deleted]]
On Mon, 8 Dec 2008, Stavros Macrakis wrote:> I've read in many places that R semantics are based on Scheme semantics. As > a long-time Lisp user and implementor, I've tried to make this more precise, > and this is what I've found so far. I've excluded trivial things that > aren't basic semantic issues: support for arbitrary-precision integers; > subscripting; general style; etc. I would appreciate corrections or > additions from more experienced users of R -- I'm sure that some of the > points below simply reflect my ignorance. > > ==Similarities to Scheme=> > R has first-class function closures. (i.e. correctly supports upward and > downward funarg). > > R has a single namespace for functions and variables (Lisp-1). > > ==Important dissimilarities to Scheme (as opposed to other Lisps)=> > R is not properly tail-recursive.True at present. May be unavoidable since the language provides access to the stack via things like sys.parent, but as it is rare to look at anything other than the immediate calling environment and call (outside of a debugging context) it may be possible to change that.> > R does not have continuations or call-with-current-continuation or other > mechanisms for implementing coroutines, general iterators, and the like. > > R supports keyword arguments. > > ==Similarities to Lisp and other dynamic languages, including Scheme=> > R is runtime-typed and garbage-collected. > > R supports nested read-eval-print loops for debugging etc. > > R expressions are represented as user-manipulable data structures. > > ==Dissimilarities to all (modern) Lisps, including Scheme=> > R has call-by-need, not call-by-object-value. > > R does not have macros.Those are related -- because of lazy evaluation one does macros are not needed to achive semantic goals (see for example tryCatch). Being able to define friendlier syntax would sometimes be nice though (see tryCatch again).> R objects are values, not pointers, so a<-1:10; b<-a; b[1]<-999; a[1] => > 999. Similarly, functions cannot modify the contents of their arguments. > > There is no equivalent to set-car!/rplaca (not even pairlists and > expressions). For example, r<-pairlist(1,2); r[[1]]<-r does not create a > circular list. And in general there doesn't seem to be substructure sharing > at the semantic level (though there may be in the implementation). > > R does not have multiple value return in the Lisp sense. > > R assignment creates a new local variable on first assignment, dynamically. > So static analysis is not enough to determine variable reference (R is not > referentially transparent). Example: ff <- function(a){if (a) x<-1; x} ; > x<-99; ff(T) -> 1; ff(F) -> 99.Correct, and a fair nuisance for code analysis and compilation work. I'm not sure how much would break if R adopted the conventions in Python (or with Scheme's define as I recall) that referencing a not yet initialized local variable is an error. I'm not sure I would label this as meaning R is not referentially transparent thoug -- that goes out the window with mutable bindings as also available in Scheme.> In R, most data types (including numeric vectors) do not have a standard > external representation which can be read back in without evaluation.The default print form is not readable in this sense but dput is available for this purpose.> R coerces logicals to numbers and numbers to strings. Lisps are stricter > about automatic type conversion -- except that false a.k.a. NIL == () in > Lisps other than Scheme.A more important difference may be that logicals can have three values -- TRUE, FALSE and NA. luke> > [[alternative HTML version deleted]] > > ______________________________________________ > R-help at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-help > PLEASE do read the posting guide http://www.R-project.org/posting-guide.html > and provide commented, minimal, self-contained, reproducible code. >-- Luke Tierney Chair, Statistics and Actuarial Science Ralph E. Wareham Professor of Mathematical Sciences University of Iowa Phone: 319-335-3386 Department of Statistics and Fax: 319-335-3017 Actuarial Science 241 Schaeffer Hall email: luke at stat.uiowa.edu Iowa City, IA 52242 WWW: http://www.stat.uiowa.edu
A few comments interspersed. On Mon, Dec 8, 2008 at 5:59 PM, Stavros Macrakis <macrakis at alum.mit.edu> wrote:> I've read in many places that R semantics are based on Scheme semantics. As > a long-time Lisp user and implementor, I've tried to make this more precise, > and this is what I've found so far. I've excluded trivial things that > aren't basic semantic issues: support for arbitrary-precision integers; > subscripting; general style; etc. I would appreciate corrections or > additions from more experienced users of R -- I'm sure that some of the > points below simply reflect my ignorance. > > ==Similarities to Scheme=> > R has first-class function closures. (i.e. correctly supports upward and > downward funarg). > > R has a single namespace for functions and variables (Lisp-1).Environments can be used to create separate name spaces. R packages can use the NAMESPACE file to set up their own namespace.> > ==Important dissimilarities to Scheme (as opposed to other Lisps)=> > R is not properly tail-recursive. > > R does not have continuations or call-with-current-continuation or other > mechanisms for implementing coroutines, general iterators, and the like. >True although there is callCC but it just lets you jump right of a nested sequence of calls.> R supports keyword arguments. > > ==Similarities to Lisp and other dynamic languages, including Scheme=> > R is runtime-typed and garbage-collected. > > R supports nested read-eval-print loops for debugging etc. > > R expressions are represented as user-manipulable data structures. > > ==Dissimilarities to all (modern) Lisps, including Scheme=> > R has call-by-need, not call-by-object-value.Call by need?> > R does not have macros.You can create them. See: Programmer's Niche: Macros in R http://cran.r-project.org/doc/Rnews/Rnews_2001-3.pdf> > R objects are values, not pointers, so a<-1:10; b<-a; b[1]<-999; a[1] => > 999. Similarly, functions cannot modify the contents of their arguments. >a[1] is not 999 after the above completes (if that is what is meant by a[1] => 999):> a<-1:10; b<-a; b[1]<-999 > a[1] 1 2 3 4 5 6 7 8 9 10> There is no equivalent to set-car!/rplaca (not even pairlists and > expressions). For example, r<-pairlist(1,2); r[[1]]<-r does not create a > circular list. And in general there doesn't seem to be substructure sharing > at the semantic level (though there may be in the implementation). > > R does not have multiple value return in the Lisp sense.You can do this: http://finzi.psych.upenn.edu/R/Rhelp02a/archive/36820.html> R assignment creates a new local variable on first assignment, dynamically. > So static analysis is not enough to determine variable reference (R is not > referentially transparent). Example: ff <- function(a){if (a) x<-1; x} ; > x<-99; ff(T) -> 1; ff(F) -> 99. > > In R, most data types (including numeric vectors) do not have a standard > external representation which can be read back in without evaluation.???> > R coerces logicals to numbers and numbers to strings. Lisps are stricter > about automatic type conversion -- except that false a.k.a. NIL == () in > Lisps other than Scheme.
Stavros Macrakis wrote:> I've read in many places that R semantics are based on Scheme semantics. As > a long-time Lisp user and implementor, I've tried to make this more precise, > and this is what I've found so far. I've excluded trivial things that > aren't basic semantic issues: support for arbitrary-precision integers; > subscripting; general style; etc. I would appreciate corrections or > additions from more experienced users of R -- I'm sure that some of the > points below simply reflect my ignorance. > > ==Similarities to Scheme=> > R has first-class function closures. (i.e. correctly supports upward and > downward funarg). > > R has a single namespace for functions and variables (Lisp-1). > > ==Important dissimilarities to Scheme (as opposed to other Lisps)=> > R is not properly tail-recursive. > > R does not have continuations or call-with-current-continuation or other > mechanisms for implementing coroutines, general iterators, and the like. >there is callCC, for example, which however seems kind of obsolete.> R supports keyword arguments. > > ==Similarities to Lisp and other dynamic languages, including Scheme=> > R is runtime-typed and garbage-collected. > > R supports nested read-eval-print loops for debugging etc. > > R expressions are represented as user-manipulable data structures. > > ==Dissimilarities to all (modern) Lisps, including Scheme=> > R has call-by-need, not call-by-object-value. > > R does not have macros. > > R objects are values, not pointers, so a<-1:10; b<-a; b[1]<-999; a[1] => > 999. Similarly, functions cannot modify the contents of their arguments. >have you actually tried this code? even if the objects are values not pointers, assignment causes, in cases such as the above, copying the value with modifications applied as needed. thus, a[1] -> 1, not 999, even though after b<-a b and a are the same value object. try the following: system.time(x<-1:(10^8)) system.time(y<-x) system.time(y[1]<-0) system.time(y[2]<-0) head(x) head(y) with some trickery, functions can modify the contents of their arguments, using deparse/substitute and assign: a <- 1 f <- function(x) assign(deparse(substitute(x)), 0, parent.frame()) f(a) a the 'cannot modify the contents' does not apply to arguments that are environments: e <- new.env(parent=emptyenv()) l <- list() f <- function(e) e$a = 0 f(e) e$a f(l) l$a> There is no equivalent to set-car!/rplaca (not even pairlists and > expressions). For example, r<-pairlist(1,2); r[[1]]<-r does not create a > circular list. And in general there doesn't seem to be substructure sharing > at the semantic level (though there may be in the implementation). >computations on environment objects seem not to be subject to the copy-value-on-assignment semantics: e <- new.env(parent=emptyenv()) ee <- e e$a <- 0 ee$a> R does not have multiple value return in the Lisp sense. > > R assignment creates a new local variable on first assignment, dynamically. > So static analysis is not enough to determine variable reference (R is not > referentially transparent). Example: ff <- function(a){if (a) x<-1; x} ; > x<-99; ff(T) -> 1; ff(F) -> 99. > > In R, most data types (including numeric vectors) do not have a standard > external representation which can be read back in without evaluation. > > R coerces logicals to numbers and numbers to strings. Lisps are stricter > about automatic type conversion -- except that false a.k.a. NIL == () in > Lisps other than Scheme. >types are not treated coherently. in some situations, r coerces doubles to complex (according to the hierarchy of types specified here and there in the man pages), in others it won't: x <- as.double(-1) y <- as.complex(-1) x == y sqrt(x) sqrt(y) in certain cases, r will also do implicit inverse (downward) coercion: is(y:y) vQ
Stavros Macrakis wrote:> There is no equivalent to set-car!/rplaca (not even pairlists and > expressions). For example, r<-pairlist(1,2); r[[1]]<-r does not create a > circular list. And in general there doesn't seem to be substructure sharing > at the semantic level (though there may be in the implementation). > >again, you can achieve the effect with environments: e = new.env(parent=emptyenv()) e$e = e e e$e$e$e vQ