Re: [Rd] List comprehensions for R

2007-12-09 Thread Gabor Grothendieck
That seems quite nice.

Note that there has been some related code posted.  See:
http://tolstoy.newcastle.edu.au/R/help/03b/6406.html
which discusses some R idioms for list comprehensions.

Also the gsubfn package has some functionality in this direction.  We
preface any function with fn$ to allow functions in its arguments
to be specified as formulas.  Its more R-ish than your code and
applies to more than just list comprehensions while your code is
more faithful to list comprehensions.

> library(gsubfn)
> fn$sapply(0:11/11, ~ sin(x))
 [1] 0. 0.09078392 0.18081808 0.26935891 0.35567516 0.43905397
 [7] 0.51880673 0.59427479 0.66483486 0.72990422 0.78894546 0.84147098
> fn$sapply(0:4, y ~ fn$sapply(0:3, x ~ x*y))
 [,1] [,2] [,3] [,4] [,5]
[1,]00000
[2,]01234
[3,]02468
[4,]0369   12
> fn$sapply(0:4, y ~ fn$sapply(0:y, x ~ x*y))
[[1]]
[1] 0

[[2]]
[1] 0 1

[[3]]
[1] 0 2 4

[[4]]
[1] 0 3 6 9

[[5]]
[1]  0  4  8 12 16

> unlist(fn$sapply(1:4, y ~ fn$sapply(1:y, x ~ x*y)))
 [1]  1  2  4  3  6  9  4  8 12 16


On Dec 9, 2007 4:41 PM, David C. Norris
<[EMAIL PROTECTED]> wrote:
> Below is code that introduces a list comprehension syntax into R,
> allowing expressions like:
>
>  > .[ sin(x) ~ x <- (0:11)/11 ]
>  [1] 0. 0.09078392 0.18081808 0.26935891 0.35567516 0.43905397
>  [7] 0.51880673 0.59427479 0.66483486 0.72990422 0.78894546 0.84147098
>  > .[ .[x*y ~ x <- 0:3] ~ y <- 0:4]
> [,1] [,2] [,3] [,4] [,5]
> [1,]00000
> [2,]01234
> [3,]02468
> [4,]0369   12
>  > .[ .[x+y ~ x <- 0:y] ~ y <- 0:4]
> [[1]]
> [1] 0
>
> [[2]]
> [1] 1 2
>
> [[3]]
> [1] 2 3 4
>
> [[4]]
> [1] 3 4 5 6
>
> [[5]]
> [1] 4 5 6 7 8
>
>  > .[ x*y ~ {x <- 1:4; y<-1:x} ]
>  [1]  1  2  4  3  6  9  4  8 12 16
>
> These constructions are supported by the following code.
>
> Regards,
> David
>
> ##
> ## Define syntax for list/vector/array comprehensions
> ##
>
> . <<- structure(NA, class="comprehension")
>
> comprehend <- function(expr, vars, seqs, comprehension=list()){
>  if(length(vars)==0) # base case
>comprehension[[length(comprehension)+1]] <- eval(expr)
>  else
>for(elt in eval(seqs[[1]])){
>  assign(vars[1], elt, inherits=TRUE)
>  comprehension <- comprehend(expr, vars[-1], seqs[-1], comprehension)
>}
>  comprehension
> }
>
> ## Support general syntax like .[{exprs} ~ {generators}]
> "[.comprehension" <- function(x, f){
>  f <- substitute(f)
>  ## To allow omission of braces around a lone comprehension generator,
>  ## as in 'expr ~ var <- seq' we make allowances for two shapes of f:
>  ##
>  ## (1)(`<-` (`~` expr
>  ##   var)
>  ##  seq)
>  ## and
>  ##
>  ## (2)(`~` expr
>  ## (`{` (`<-` var1 seq1)
>  ##  (`<-` var2 seq2)
>  ##  ...
>  ##  (`<-` varN <- seqN)))
>  ##
>  ## In the former case, we set gens <- list(var <- seq), unifying the
>  ## treatment of both shapes under the latter, more general one.
>  syntax.error <- "Comprehension expects 'expr ~ {x1 <- seq1; ... ; xN
> <- seqN}'."
>  if(!is.call(f) || (f[[1]]!='<-' && f[[1]]!='~'))
>stop(syntax.error)
>  if(is(f,'<-')){ # (1)
>lhs <- f[[2]]
>if(!is.call(lhs) || lhs[[1]] != '~')
>  stop(syntax.error)
>expr <- lhs[[2]]
>var <- as.character(lhs[[3]])
>seq <- f[[3]]
>gens <- list(call('<-', var, seq))
>  } else { # (2)
>expr <- f[[2]]
>gens <- as.list(f[[3]])[-1]
>if(any(lapply(gens, class) != '<-'))
>  stop(syntax.error)
>  }
>  ## Fill list comprehension .LC
>  vars <- as.character(lapply(gens, function(g) g[[2]]))
>  seqs <- lapply(gens, function(g) g[[3]])
>  .LC <- comprehend(expr, vars, seqs)
>  ## Provided the result is rectangular, convert it to a vector or array
>  ## TODO: Extend to handle .LC structures more than 2-deep.
>  if(!length(.LC))
>return(.LC)
>  dim1 <- dim(.LC[[1]])
>  if(is.null(dim1)){
>lengths <- sapply(.LC, length)
>if(all(lengths == lengths[1])){ # rectangular
>  .LC <- unlist(.LC)
>  if(lengths[1] > 1) # matrix
>dim(.LC) <- c(lengths[1], length(lengths))
>} else { # ragged
>  # leave .LC as a list
>}
>  } else { # elements of .LC have dimension
>dim <- c(dim1, length(.LC))
>.LC <- unlist(.LC)
>dim(.LC) <- dim
>  }
>  .LC
> }
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] List comprehensions for R

2007-12-09 Thread David C. Norris
Below is code that introduces a list comprehension syntax into R, 
allowing expressions like:

 > .[ sin(x) ~ x <- (0:11)/11 ]
 [1] 0. 0.09078392 0.18081808 0.26935891 0.35567516 0.43905397
 [7] 0.51880673 0.59427479 0.66483486 0.72990422 0.78894546 0.84147098
 > .[ .[x*y ~ x <- 0:3] ~ y <- 0:4]
 [,1] [,2] [,3] [,4] [,5]
[1,]00000
[2,]01234
[3,]02468
[4,]0369   12
 > .[ .[x+y ~ x <- 0:y] ~ y <- 0:4]
[[1]]
[1] 0

[[2]]
[1] 1 2

[[3]]
[1] 2 3 4

[[4]]
[1] 3 4 5 6

[[5]]
[1] 4 5 6 7 8

 > .[ x*y ~ {x <- 1:4; y<-1:x} ]
 [1]  1  2  4  3  6  9  4  8 12 16

These constructions are supported by the following code.

Regards,
David

##
## Define syntax for list/vector/array comprehensions
##

. <<- structure(NA, class="comprehension")

comprehend <- function(expr, vars, seqs, comprehension=list()){
  if(length(vars)==0) # base case
comprehension[[length(comprehension)+1]] <- eval(expr)
  else
for(elt in eval(seqs[[1]])){
  assign(vars[1], elt, inherits=TRUE)
  comprehension <- comprehend(expr, vars[-1], seqs[-1], comprehension)
}
  comprehension
}

## Support general syntax like .[{exprs} ~ {generators}]
"[.comprehension" <- function(x, f){
  f <- substitute(f)
  ## To allow omission of braces around a lone comprehension generator,
  ## as in 'expr ~ var <- seq' we make allowances for two shapes of f:
  ##
  ## (1)(`<-` (`~` expr
  ##   var)
  ##  seq)
  ## and
  ##
  ## (2)(`~` expr
  ## (`{` (`<-` var1 seq1)
  ##  (`<-` var2 seq2)
  ##  ...
  ##  (`<-` varN <- seqN)))
  ##
  ## In the former case, we set gens <- list(var <- seq), unifying the
  ## treatment of both shapes under the latter, more general one.
  syntax.error <- "Comprehension expects 'expr ~ {x1 <- seq1; ... ; xN 
<- seqN}'."
  if(!is.call(f) || (f[[1]]!='<-' && f[[1]]!='~'))
stop(syntax.error)
  if(is(f,'<-')){ # (1)
lhs <- f[[2]]
if(!is.call(lhs) || lhs[[1]] != '~')
  stop(syntax.error)
expr <- lhs[[2]]
var <- as.character(lhs[[3]])
seq <- f[[3]]
gens <- list(call('<-', var, seq))
  } else { # (2)
expr <- f[[2]]
gens <- as.list(f[[3]])[-1]
if(any(lapply(gens, class) != '<-'))
  stop(syntax.error)
  }
  ## Fill list comprehension .LC
  vars <- as.character(lapply(gens, function(g) g[[2]]))
  seqs <- lapply(gens, function(g) g[[3]])
  .LC <- comprehend(expr, vars, seqs)
  ## Provided the result is rectangular, convert it to a vector or array
  ## TODO: Extend to handle .LC structures more than 2-deep.
  if(!length(.LC))
return(.LC)
  dim1 <- dim(.LC[[1]])
  if(is.null(dim1)){
lengths <- sapply(.LC, length)
if(all(lengths == lengths[1])){ # rectangular
  .LC <- unlist(.LC)
  if(lengths[1] > 1) # matrix
dim(.LC) <- c(lengths[1], length(lengths))
} else { # ragged
  # leave .LC as a list
}
  } else { # elements of .LC have dimension
dim <- c(dim1, length(.LC))
.LC <- unlist(.LC)
dim(.LC) <- dim
  }
  .LC
}

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Using Fortran 95 in an R package?

2007-12-09 Thread John Fox
Dear Brian,

Thank you for this.

John

> -Original Message-
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Prof Brian Ripley
> Sent: Sunday, December 09, 2007 1:05 PM
> To: John Fox
> Cc: r-devel@r-project.org
> Subject: Re: [Rd] Using Fortran 95 in an R package?
> 
> On Sun, 9 Dec 2007, John Fox wrote:
> 
> > Dear R-devel list members,
> >
> > What's the best current advice about writing Fortran code 
> for use in R 
> > packages? The Writing R Extensions manual still says that 
> the .Fortran 
> > interface is primarily intended for FORTRAN 77 code. In particular, 
> > are there portability issues if I use Fortran 95 in a package? For 
> > example, I see that Rtools for Windows now include the 
> gfortran compiler.
> 
> Yes, there are still portability issues.  We do still see 
> quite a few people using gcc3/g77 (especially on older Linux 
> and commercial Unices) and there are further issues if you 
> make use of subprogram names containing underlines.  We don't 
> distribute a cross-building solution for Windows using 
> gfortran (although one can be built, it will not be mature 
> until gcc 4.3.x is out).
> 
> However, I would not let that deter you: just use .f95 
> extensions on the Fortran 95 files and avoid underlines.  For 
> Windows users you are effectively requiring R >= 2.6.0.
> 
> Brian
> 
> -- 
> Brian D. Ripley,  [EMAIL PROTECTED]
> Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
> University of Oxford, Tel:  +44 1865 272861 (self)
> 1 South Parks Road, +44 1865 272866 (PA)
> Oxford OX1 3TG, UKFax:  +44 1865 272595
> 
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Using Fortran 95 in an R package?

2007-12-09 Thread Prof Brian Ripley
On Sun, 9 Dec 2007, John Fox wrote:

> Dear R-devel list members,
>
> What's the best current advice about writing Fortran code for use in R
> packages? The Writing R Extensions manual still says that the .Fortran
> interface is primarily intended for FORTRAN 77 code. In particular, are
> there portability issues if I use Fortran 95 in a package? For example, I
> see that Rtools for Windows now include the gfortran compiler.

Yes, there are still portability issues.  We do still see quite a few 
people using gcc3/g77 (especially on older Linux and commercial Unices) 
and there are further issues if you make use of subprogram names 
containing underlines.  We don't distribute a cross-building solution for 
Windows using gfortran (although one can be built, it will not be mature
until gcc 4.3.x is out).

However, I would not let that deter you: just use .f95 extensions on the 
Fortran 95 files and avoid underlines.  For Windows users you are 
effectively requiring R >= 2.6.0.

Brian

-- 
Brian D. Ripley,  [EMAIL PROTECTED]
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford, Tel:  +44 1865 272861 (self)
1 South Parks Road, +44 1865 272866 (PA)
Oxford OX1 3TG, UKFax:  +44 1865 272595

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Using Fortran 95 in an R package?

2007-12-09 Thread John Fox
Dear R-devel list members,

What's the best current advice about writing Fortran code for use in R
packages? The Writing R Extensions manual still says that the .Fortran
interface is primarily intended for FORTRAN 77 code. In particular, are
there portability issues if I use Fortran 95 in a package? For example, I
see that Rtools for Windows now include the gfortran compiler.

(I know that this question has come up before, but not, as far as I can see,
in the last year.)

Thanks,
 John


John Fox, Professor
Department of Sociology
McMaster University
Hamilton, Ontario
Canada L8S 4M4
905-525-9140x23604
http://socserv.mcmaster.ca/jfox

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel