Re: [Rd] withAutoprint({ .... }) ?

2016-09-27 Thread Kirill Müller

On 25.09.2016 18:29, Martin Maechler wrote:

I'm now committing my version (including (somewhat incomplete)
documentation, so you (all) can look at it and try / test it further.
Thanks, that's awesome. Is `withAutoprint()` recursive? How about 
calling the new function in `example()` (instead of `source()` as it is 
now) so that examples are always rendered in auto-print mode? That may 
add some extra output to examples (which can be removed easily), but 
solve the original problem in a painless way.



-Kirill

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


Re: [Rd] withAutoprint({ .... }) ?

2016-09-27 Thread Martin Maechler
> Henrik Bengtsson 
> on Sun, 25 Sep 2016 12:38:27 -0700 writes:

> On Sun, Sep 25, 2016 at 9:29 AM, Martin Maechler
>  wrote:
>>> Henrik Bengtsson  on
>>> Sat, 24 Sep 2016 11:31:49 -0700 writes:
>> 
>> > Martin, did you post your code for withAutoprint()
>> anywhere?  > Building withAutoprint() on top of source()
>> definitely makes sense, > unless, as Bill says, source()
>> itself could provide the same feature.
>> 
>> I was really mainly asking for advice about the function
>> name .. and got none.

> I missed that part.  I think the name is good.  A shorter
> alternative would be withEcho(), but could be a little bit
> misleading since it doesn't reflect 'print=TRUE' to
> source().

>> 
>> I'm now committing my version (including (somewhat incomplete)
>> documentation, so you (all) can look at it and try / test it further.
>> 
>> > To differentiate between withAutoprint({ x <- 1 }) and
>> > withAutoprint(expr) where is an expression / language object, one
>> > could have an optional argument `substitute=TRUE`, e.g.
>> 
>> > withAutoprint <- function(expr, substitute = TRUE, ...) {
>> >if (substitute) expr <- substitute(expr)
>> >[...]
>> > }
>> 
>> I think my approach is nicer insofar it does not seem to need
>> such an argument I'm sure you'll try to disprove that ;-)

> Nah, I like that you've extended source() with the 'exprs' argument.

> May I suggest to add:

> svn diff src/library/base/R/
> Index: src/library/base/R/source.R
> ===
> --- src/library/base/R/source.R (revision 71357)
> +++ src/library/base/R/source.R (working copy)
> @@ -198,7 +198,7 @@
> if (!tail) {
> # Deparse.  Must drop "expression(...)"
> dep <- substr(paste(deparse(ei, width.cutoff = width.cutoff,
> -control = 
"showAttributes"),
> +  control = c("keepInteger", "showAttributes")),
> collapse = "\n"), 12L, 1e+06L)
> dep <- paste0(prompt.echo,
> gsub("\n", paste0("\n", continue.echo), dep))

> such that you get:

>> withAutoprint(x <- c(1L, NA_integer_, NA))
>> x <- c(1L, NA_integer_, NA)

> because without it, you get:

>> withAutoprint(x <- c(1L, NA_integer_, NA))
>> x <- c(1, NA, NA)

That's a very good consideration.
However, your change would change the semantics of source(),
not just those of withAutoprint(), and I would not want to do
that ... at least not at the moment. 

What I've done instead, is to make this yet another new
 argument of both source() and withAutoprint(),
called   'deparseCtrl'  and with different defaults (currently)
for the 2 functions. 

Thank you for the feedback!
Martin




> Thanks,
> Henrik


>> 
>> Martin
>> 
>> > Just some thoughts
>> > /Henrik
>> 
>> 
>> > On Sat, Sep 24, 2016 at 6:37 AM, Martin Maechler
>> >  wrote:
>> >>> William Dunlap 
>> >>> on Fri, 2 Sep 2016 08:33:47 -0700 writes:
>> >>
>> >> > Re withAutoprint(), Splus's source() function could take a 
expression
>> >> > (literal or not) in place of a file name or text so it could support
>> >> > withAutoprint-like functionality in its GUI.  E.g.,
>> >>
>> >> >> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- 
log(x)
>> >> > ; x - 100}, prompt="--> ")
--> x <- 3:7
--> sum(x)
>> >> > [1] 25
--> y <- log(x)
--> x - 100
>> >> > [1] -97 -96 -95 -94 -93
>> >>
>> >> > or
>> >>
>> >> >> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
>> >> >> source(auto.print=TRUE, exprs = expr, prompt="--> ")
--> x <- 3:7
--> sum(x)
>> >> > [1] 25
--> y <- log(x)
--> x - 100
>> >> > [1] -97 -96 -95 -94 -93
>> >>
>> >> > It was easy to implement, since exprs's default value is 
parse(file) or
>> >> > parse(text=text), which source is calculating anyway.
>> >>
>> >>
>> >> > Bill Dunlap
>> >> > TIBCO Software
>> >> > wdunlap tibco.com
>> >>
>> >> Thank you, Bill  (and the other correspondents); that's indeed a
>> >> very good suggestion :
>> >>
>> >> I've come to the conclusion that Duncan and Bill are right:  One
>> >> should do this in R (not C) and as Bill hinted, one should use
>> >> source().  I first tried to do it separately, just "like source()",
>> >> but a considerable part of the source of source()  {:-)} is
>> >> about using src attributes instead of deparse() when the former
>> >> are present,  and it does make sense to generalize
>> >> withAutoprint() to have the same feature, so after all, have it
>> >> 

Re: [Rd] withAutoprint({ .... }) ?

2016-09-25 Thread Henrik Bengtsson
On Sun, Sep 25, 2016 at 9:29 AM, Martin Maechler
 wrote:
>> Henrik Bengtsson 
>> on Sat, 24 Sep 2016 11:31:49 -0700 writes:
>
> > Martin, did you post your code for withAutoprint() anywhere?
> > Building withAutoprint() on top of source() definitely makes sense,
> > unless, as Bill says, source() itself could provide the same feature.
>
> I was really mainly asking for advice about the function name
> .. and got none.

I missed that part.  I think the name is good.  A shorter alternative
would be withEcho(), but could be a little bit misleading since it
doesn't reflect 'print=TRUE' to source().

>
> I'm now committing my version (including (somewhat incomplete)
> documentation, so you (all) can look at it and try / test it further.
>
> > To differentiate between withAutoprint({ x <- 1 }) and
> > withAutoprint(expr) where is an expression / language object, one
> > could have an optional argument `substitute=TRUE`, e.g.
>
> > withAutoprint <- function(expr, substitute = TRUE, ...) {
> >if (substitute) expr <- substitute(expr)
> >[...]
> > }
>
> I think my approach is nicer insofar it does not seem to need
> such an argument I'm sure you'll try to disprove that ;-)

Nah, I like that you've extended source() with the 'exprs' argument.

May I suggest to add:

svn diff src/library/base/R/
Index: src/library/base/R/source.R
===
--- src/library/base/R/source.R (revision 71357)
+++ src/library/base/R/source.R (working copy)
@@ -198,7 +198,7 @@
  if (!tail) {
 # Deparse.  Must drop "expression(...)"
 dep <- substr(paste(deparse(ei, width.cutoff = width.cutoff,
-control = "showAttributes"),
+  control = c("keepInteger", "showAttributes")),
  collapse = "\n"), 12L, 1e+06L)
 dep <- paste0(prompt.echo,
   gsub("\n", paste0("\n", continue.echo), dep))

such that you get:

> withAutoprint(x <- c(1L, NA_integer_, NA))
> x <- c(1L, NA_integer_, NA)

because without it, you get:

> withAutoprint(x <- c(1L, NA_integer_, NA))
> x <- c(1, NA, NA)

Thanks,

Henrik


>
> Martin
>
> > Just some thoughts
> > /Henrik
>
>
> > On Sat, Sep 24, 2016 at 6:37 AM, Martin Maechler
> >  wrote:
> >>> William Dunlap 
> >>> on Fri, 2 Sep 2016 08:33:47 -0700 writes:
> >>
> >> > Re withAutoprint(), Splus's source() function could take a expression
> >> > (literal or not) in place of a file name or text so it could support
> >> > withAutoprint-like functionality in its GUI.  E.g.,
> >>
> >> >> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- 
> log(x)
> >> > ; x - 100}, prompt="--> ")
> --> x <- 3:7
> --> sum(x)
> >> > [1] 25
> --> y <- log(x)
> --> x - 100
> >> > [1] -97 -96 -95 -94 -93
> >>
> >> > or
> >>
> >> >> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
> >> >> source(auto.print=TRUE, exprs = expr, prompt="--> ")
> --> x <- 3:7
> --> sum(x)
> >> > [1] 25
> --> y <- log(x)
> --> x - 100
> >> > [1] -97 -96 -95 -94 -93
> >>
> >> > It was easy to implement, since exprs's default value is parse(file) 
> or
> >> > parse(text=text), which source is calculating anyway.
> >>
> >>
> >> > Bill Dunlap
> >> > TIBCO Software
> >> > wdunlap tibco.com
> >>
> >> Thank you, Bill  (and the other correspondents); that's indeed a
> >> very good suggestion :
> >>
> >> I've come to the conclusion that Duncan and Bill are right:  One
> >> should do this in R (not C) and as Bill hinted, one should use
> >> source().  I first tried to do it separately, just "like source()",
> >> but a considerable part of the source of source()  {:-)} is
> >> about using src attributes instead of deparse() when the former
> >> are present,  and it does make sense to generalize
> >> withAutoprint() to have the same feature, so after all, have it
> >> call source().
> >>
> >> I've spent a few hours now trying things and variants, also
> >> found I needed to enhance source()  very slightly also in a few
> >> other details, and now (in my uncommitted version of R-devel),
> >>
> >> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
> >>
> >> produces
> >>
> >>> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
> >>> x <- 1:12
> >>> x - 1
> >> [1]  0  1  2  3  4  5  6  7  8  9 10 11
> >>> (y <- (x - 5)^2)
> >> [1] 16  9  4  1  0  1  4  9 16 25 36 49
> >>> z <- y
> >>> z - 10
> >> [1]   6  -1  -6  -9 -10  -9  -6  -1   6  15  26  39
> >>>
> >>
> >> and is equivalent to
> >>
> >> withAutoprint(expression(x <- 1:12, x-1, (y <- (x-5)^2), z <- y, z 

Re: [Rd] withAutoprint({ .... }) ?

2016-09-25 Thread Martin Maechler
> Henrik Bengtsson 
> on Sat, 24 Sep 2016 11:31:49 -0700 writes:

> Martin, did you post your code for withAutoprint() anywhere?
> Building withAutoprint() on top of source() definitely makes sense,
> unless, as Bill says, source() itself could provide the same feature.

I was really mainly asking for advice about the function name
.. and got none.

I'm now committing my version (including (somewhat incomplete)
documentation, so you (all) can look at it and try / test it further.

> To differentiate between withAutoprint({ x <- 1 }) and
> withAutoprint(expr) where is an expression / language object, one
> could have an optional argument `substitute=TRUE`, e.g.

> withAutoprint <- function(expr, substitute = TRUE, ...) {
>if (substitute) expr <- substitute(expr)
>[...]
> }

I think my approach is nicer insofar it does not seem to need
such an argument I'm sure you'll try to disprove that ;-)

Martin

> Just some thoughts
> /Henrik


> On Sat, Sep 24, 2016 at 6:37 AM, Martin Maechler
>  wrote:
>>> William Dunlap 
>>> on Fri, 2 Sep 2016 08:33:47 -0700 writes:
>> 
>> > Re withAutoprint(), Splus's source() function could take a expression
>> > (literal or not) in place of a file name or text so it could support
>> > withAutoprint-like functionality in its GUI.  E.g.,
>> 
>> >> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- 
log(x)
>> > ; x - 100}, prompt="--> ")
--> x <- 3:7
--> sum(x)
>> > [1] 25
--> y <- log(x)
--> x - 100
>> > [1] -97 -96 -95 -94 -93
>> 
>> > or
>> 
>> >> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
>> >> source(auto.print=TRUE, exprs = expr, prompt="--> ")
--> x <- 3:7
--> sum(x)
>> > [1] 25
--> y <- log(x)
--> x - 100
>> > [1] -97 -96 -95 -94 -93
>> 
>> > It was easy to implement, since exprs's default value is parse(file) or
>> > parse(text=text), which source is calculating anyway.
>> 
>> 
>> > Bill Dunlap
>> > TIBCO Software
>> > wdunlap tibco.com
>> 
>> Thank you, Bill  (and the other correspondents); that's indeed a
>> very good suggestion :
>> 
>> I've come to the conclusion that Duncan and Bill are right:  One
>> should do this in R (not C) and as Bill hinted, one should use
>> source().  I first tried to do it separately, just "like source()",
>> but a considerable part of the source of source()  {:-)} is
>> about using src attributes instead of deparse() when the former
>> are present,  and it does make sense to generalize
>> withAutoprint() to have the same feature, so after all, have it
>> call source().
>> 
>> I've spent a few hours now trying things and variants, also
>> found I needed to enhance source()  very slightly also in a few
>> other details, and now (in my uncommitted version of R-devel),
>> 
>> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
>> 
>> produces
>> 
>>> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
>>> x <- 1:12
>>> x - 1
>> [1]  0  1  2  3  4  5  6  7  8  9 10 11
>>> (y <- (x - 5)^2)
>> [1] 16  9  4  1  0  1  4  9 16 25 36 49
>>> z <- y
>>> z - 10
>> [1]   6  -1  -6  -9 -10  -9  -6  -1   6  15  26  39
>>> 
>> 
>> and is equivalent to
>> 
>> withAutoprint(expression(x <- 1:12, x-1, (y <- (x-5)^2), z <- y, z - 10 
))
>> 
>> I don't see any way around the "mis-feature" that all "input"
>> expressions are in the end shown twice in the "output" (the
>> first time by showing the withAutoprint(...) call itself).
>> 
>> The function *name* is "not bad" but also a bit longish;
>> maybe there are better ideas?  (not longer, no "_" - I know this
>> is a matter of taste only)
>> 
>> Martin
>> 
>> > On Fri, Sep 2, 2016 at 4:56 AM, Martin Maechler 

>> > wrote:
>> 
>> >> On R-help, with subject
>> >> '[R] source() does not include added code'
>> >>
>> >> > Joshua Ulrich 
>> >> > on Wed, 31 Aug 2016 10:35:01 -0500 writes:
>> >>
>> >> > I have quantstrat installed and it works fine for me.  If you're
>> >> > asking why the output of t(tradeStats('macross')) isn't being
>> >> printed,
>> >> > that's because of what's described in the first paragraph in the
>> >> > *Details* section of help("source"):
>> >>
>> >> > Note that running code via ‘source’ differs in a few respects from
>> >> > entering it at the R command line.  Since expressions are not
>> >> > executed at the top level, auto-printing is not done.  So you will
>> >> > need to include explicit ‘print’ calls for things you 

Re: [Rd] withAutoprint({ .... }) ?

2016-09-24 Thread Henrik Bengtsson
Martin, did you post your code for withAutoprint() anywhere?

Building withAutoprint() on top of source() definitely makes sense,
unless, as Bill says, source() itself could provide the same feature.

To differentiate between withAutoprint({ x <- 1 }) and
withAutoprint(expr) where is an expression / language object, one
could have an optional argument `substitute=TRUE`, e.g.

withAutoprint <- function(expr, substitute = TRUE, ...) {
  if (substitute) expr <- substitute(expr)
  [...]
}

Just some thoughts

/Henrik


On Sat, Sep 24, 2016 at 6:37 AM, Martin Maechler
 wrote:
>> William Dunlap 
>> on Fri, 2 Sep 2016 08:33:47 -0700 writes:
>
> > Re withAutoprint(), Splus's source() function could take a expression
> > (literal or not) in place of a file name or text so it could support
> > withAutoprint-like functionality in its GUI.  E.g.,
>
> >> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- 
> log(x)
> > ; x - 100}, prompt="--> ")
> --> x <- 3:7
> --> sum(x)
> > [1] 25
> --> y <- log(x)
> --> x - 100
> > [1] -97 -96 -95 -94 -93
>
> > or
>
> >> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
> >> source(auto.print=TRUE, exprs = expr, prompt="--> ")
> --> x <- 3:7
> --> sum(x)
> > [1] 25
> --> y <- log(x)
> --> x - 100
> > [1] -97 -96 -95 -94 -93
>
> > It was easy to implement, since exprs's default value is parse(file) or
> > parse(text=text), which source is calculating anyway.
>
>
> > Bill Dunlap
> > TIBCO Software
> > wdunlap tibco.com
>
> Thank you, Bill  (and the other correspondents); that's indeed a
> very good suggestion :
>
> I've come to the conclusion that Duncan and Bill are right:  One
> should do this in R (not C) and as Bill hinted, one should use
> source().  I first tried to do it separately, just "like source()",
> but a considerable part of the source of source()  {:-)} is
> about using src attributes instead of deparse() when the former
> are present,  and it does make sense to generalize
> withAutoprint() to have the same feature, so after all, have it
> call source().
>
> I've spent a few hours now trying things and variants, also
> found I needed to enhance source()  very slightly also in a few
> other details, and now (in my uncommitted version of R-devel),
>
>   withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
>
> produces
>
>> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
>> x <- 1:12
>> x - 1
>  [1]  0  1  2  3  4  5  6  7  8  9 10 11
>> (y <- (x - 5)^2)
>  [1] 16  9  4  1  0  1  4  9 16 25 36 49
>> z <- y
>> z - 10
>  [1]   6  -1  -6  -9 -10  -9  -6  -1   6  15  26  39
>>
>
> and is equivalent to
>
>withAutoprint(expression(x <- 1:12, x-1, (y <- (x-5)^2), z <- y, z - 10 ))
>
> I don't see any way around the "mis-feature" that all "input"
> expressions are in the end shown twice in the "output" (the
> first time by showing the withAutoprint(...) call itself).
>
> The function *name* is "not bad" but also a bit longish;
> maybe there are better ideas?  (not longer, no "_" - I know this
> is a matter of taste only)
>
> Martin
>
> > On Fri, Sep 2, 2016 at 4:56 AM, Martin Maechler 
> 
> > wrote:
>
> >> On R-help, with subject
> >> '[R] source() does not include added code'
> >>
> >> > Joshua Ulrich 
> >> > on Wed, 31 Aug 2016 10:35:01 -0500 writes:
> >>
> >> > I have quantstrat installed and it works fine for me.  If you're
> >> > asking why the output of t(tradeStats('macross')) isn't being
> >> printed,
> >> > that's because of what's described in the first paragraph in the
> >> > *Details* section of help("source"):
> >>
> >> > Note that running code via ‘source’ differs in a few respects from
> >> > entering it at the R command line.  Since expressions are not
> >> > executed at the top level, auto-printing is not done.  So you will
> >> > need to include explicit ‘print’ calls for things you want to be
> >> > printed (and remember that this includes plotting by ‘lattice’,
> >> > FAQ Q7.22).
> >>
> >>
> >>
> >> > So you need:
> >>
> >> > print(t(tradeStats('macross')))
> >>
> >> > if you want the output printed to the console.
> >>
> >> indeed, and "of course"" ;-)
> >>
> >> As my subject indicates, this is another case, where it would be
> >> very convenient to have a function
> >>
> >> withAutoprint()
> >>
> >> so the OP could have (hopefully) have used
> >> withAutoprint(source(..))
> >> though that would have been equivalent to the already nicely existing
> >>
> >> source(.., print.eval = TRUE)
> >>
> >> which works via the  withVisible(.) utility that returns for each
> >> 

Re: [Rd] withAutoprint({ .... }) ?

2016-09-24 Thread Martin Maechler
> William Dunlap 
> on Fri, 2 Sep 2016 08:33:47 -0700 writes:

> Re withAutoprint(), Splus's source() function could take a expression
> (literal or not) in place of a file name or text so it could support
> withAutoprint-like functionality in its GUI.  E.g.,

>> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- log(x)
> ; x - 100}, prompt="--> ")
--> x <- 3:7
--> sum(x)
> [1] 25
--> y <- log(x)
--> x - 100
> [1] -97 -96 -95 -94 -93

> or

>> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
>> source(auto.print=TRUE, exprs = expr, prompt="--> ")
--> x <- 3:7
--> sum(x)
> [1] 25
--> y <- log(x)
--> x - 100
> [1] -97 -96 -95 -94 -93

> It was easy to implement, since exprs's default value is parse(file) or
> parse(text=text), which source is calculating anyway.


> Bill Dunlap
> TIBCO Software
> wdunlap tibco.com

Thank you, Bill  (and the other correspondents); that's indeed a
very good suggestion :

I've come to the conclusion that Duncan and Bill are right:  One
should do this in R (not C) and as Bill hinted, one should use
source().  I first tried to do it separately, just "like source()",
but a considerable part of the source of source()  {:-)} is
about using src attributes instead of deparse() when the former
are present,  and it does make sense to generalize
withAutoprint() to have the same feature, so after all, have it
call source().

I've spent a few hours now trying things and variants, also
found I needed to enhance source()  very slightly also in a few
other details, and now (in my uncommitted version of R-devel), 

  withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })

produces

> withAutoprint({ x <- 1:12; x-1; (y <- (x-5)^2); z <- y; z - 10 })
> x <- 1:12
> x - 1
 [1]  0  1  2  3  4  5  6  7  8  9 10 11
> (y <- (x - 5)^2)
 [1] 16  9  4  1  0  1  4  9 16 25 36 49
> z <- y
> z - 10
 [1]   6  -1  -6  -9 -10  -9  -6  -1   6  15  26  39
> 

and is equivalent to 

   withAutoprint(expression(x <- 1:12, x-1, (y <- (x-5)^2), z <- y, z - 10 ))

I don't see any way around the "mis-feature" that all "input"
expressions are in the end shown twice in the "output" (the
first time by showing the withAutoprint(...) call itself).

The function *name* is "not bad" but also a bit longish;
maybe there are better ideas?  (not longer, no "_" - I know this
is a matter of taste only)

Martin

> On Fri, Sep 2, 2016 at 4:56 AM, Martin Maechler 

> wrote:

>> On R-help, with subject
>> '[R] source() does not include added code'
>> 
>> > Joshua Ulrich 
>> > on Wed, 31 Aug 2016 10:35:01 -0500 writes:
>> 
>> > I have quantstrat installed and it works fine for me.  If you're
>> > asking why the output of t(tradeStats('macross')) isn't being
>> printed,
>> > that's because of what's described in the first paragraph in the
>> > *Details* section of help("source"):
>> 
>> > Note that running code via ‘source’ differs in a few respects from
>> > entering it at the R command line.  Since expressions are not
>> > executed at the top level, auto-printing is not done.  So you will
>> > need to include explicit ‘print’ calls for things you want to be
>> > printed (and remember that this includes plotting by ‘lattice’,
>> > FAQ Q7.22).
>> 
>> 
>> 
>> > So you need:
>> 
>> > print(t(tradeStats('macross')))
>> 
>> > if you want the output printed to the console.
>> 
>> indeed, and "of course"" ;-)
>> 
>> As my subject indicates, this is another case, where it would be
>> very convenient to have a function
>> 
>> withAutoprint()
>> 
>> so the OP could have (hopefully) have used
>> withAutoprint(source(..))
>> though that would have been equivalent to the already nicely existing
>> 
>> source(.., print.eval = TRUE)
>> 
>> which works via the  withVisible(.) utility that returns for each
>> 'expression' if it would auto print or not, and then does print (or
>> not) accordingly.
>> 
>> My own use cases for such a withAutoprint({...})
>> are demos and examples, sometimes even package tests which I want to 
print:
>> 
>> Assume I have a nice demo / example on a help page/ ...
>> 
>> foo(..)
>> (z <- bar(..))
>> summary(z)
>> 
>> 
>> where I carefully do print parts (and don't others),
>> and suddenly I find I want to run that part of the demo /
>> example / test only in some circumstances, e.g., only when
>> interactive, but not in BATCH, or only if it is me, the package 
maintainer,
>> 
>> if( identical(Sys.getenv("USER"), "maechler") ) {
>> foo(..)
>> (z <- bar(..))
>> summary(z)
>> 
>> }
>> 
>> 

Re: [Rd] withAutoprint({ .... }) ?

2016-09-02 Thread luke-tierney

On Fri, 2 Sep 2016, Kirill Müller wrote:


On 02.09.2016 14:38, Duncan Murdoch wrote:

On 02/09/2016 7:56 AM, Martin Maechler wrote:

On R-help, with subject
   '[R] source() does not include added code'


Joshua Ulrich 
on Wed, 31 Aug 2016 10:35:01 -0500 writes:


> I have quantstrat installed and it works fine for me. If you're
> asking why the output of t(tradeStats('macross')) isn't being 
printed,

> that's because of what's described in the first paragraph in the
> *Details* section of help("source"):

> Note that running code via ‘source’ differs in a few respects from
> entering it at the R command line.  Since expressions are not
> executed at the top level, auto-printing is not done. So you will
> need to include explicit ‘print’ calls for things you want to be
> printed (and remember that this includes plotting by ‘lattice’,
> FAQ Q7.22).



> So you need:

> print(t(tradeStats('macross')))

> if you want the output printed to the console.

indeed, and "of course"" ;-)

As my subject indicates, this is another case, where it would be
very convenient to have a function

   withAutoprint()

so the OP could have (hopefully) have used
   withAutoprint(source(..))
though that would have been equivalent to the already nicely existing

   source(.., print.eval = TRUE)

which works via the  withVisible(.) utility that returns for each
'expression' if it would auto print or not, and then does print (or
not) accordingly.

My own use cases for such a withAutoprint({...})
are demos and examples, sometimes even package tests which I want to 
print:


Assume I have a nice demo / example on a help page/ ...

foo(..)
(z <- bar(..))
summary(z)


where I carefully do print parts (and don't others),
and suddenly I find I want to run that part of the demo /
example / test only in some circumstances, e.g., only when
interactive, but not in BATCH, or only if it is me, the package 
maintainer,


if( identical(Sys.getenv("USER"), "maechler") ) {
  foo(..)
  (z <- bar(..))
  summary(z)
  
}

Now all the auto-printing is gone, and

1) I have to find out which of these function calls do autoprint and 
wrap

   a print(..) around these, and

2) the result is quite ugly (for an example on a help page etc.)

What I would like in a future R, is to be able to simply wrap the "{
.. } above with an 'withAutoprint(.) :

if( identical(Sys.getenv("USER"), "maechler") ) withAutoprint({
  foo(..)
  (z <- bar(..))
  summary(z)
  
})

Conceptually such a function could be written similar to source() 
with an R
level for loop, treating each expression separately, calling eval(.) 
etc.
That may cost too much performnace, ... still to have it would be 
better than

not having the possibility.



If you read so far, you'd probably agree that such a function
could be a nice asset in R,
notably if it was possible to do this on the fast C level of R's main
REPL.

Have any of you looked into how this could be provided in R ?
If you know the source a little, you will remember that there's
the global variable  R_Visible  which is crucial here.
The problem with that is that it *is* global, and only available
as that; that the auto-printing "concept" is so linked to "toplevel 
context"
and that is not easy, and AFAIK not so much centralized in one place 
in the
source. Consequently, all kind of (very) low level functions 
manipulate R_Visible

temporarily and so a C level implementation of withAutoprint() may
need considerable more changes than just setting R_Visible to TRUE in 
one

place.

Have any efforts / experiments already happened towards providing such
functionality ?


I don't think the performance cost would matter.  If you're printing 
something, you're already slow.  So doing this at the R level would 
make most sense to me --- that's how Sweave and source and knitr do 
it, so it can't be that bad.


Duncan Murdoch

A C-level implementation would bring the benefit of a lean traceback() 
in case of an error. I suspect eval() could be enhanced to auto-print.


By the same token it would be extremely helpful to have a C-level 
implementation of local() which wouldn't litter the stack trace.


local() within a byte compiled function already produces a less
cluttered traceback, though perhaps not ideal. Moving the interpreted
version closer to the compiled one is in the works.

Best,

luke




-Kirill

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


--
Luke Tierney
Ralph E. Wareham Professor of Mathematical Sciences
University of Iowa  Phone: 319-335-3386
Department of Statistics andFax:   319-335-3017
   Actuarial Science
241 Schaeffer Hall  email:   luke-tier...@uiowa.edu
Iowa City, IA 52242 WWW:  http://www.stat.uiowa.edu
__

Re: [Rd] withAutoprint({ .... }) ?

2016-09-02 Thread William Dunlap via R-devel
Re withAutoprint(), Splus's source() function could take a expression
(literal or not) in place of a file name or text so it could support
withAutoprint-like functionality in its GUI.  E.g.,

> source(auto.print=TRUE, exprs.literal= { x <- 3:7 ; sum(x) ; y <- log(x)
; x - 100}, prompt="--> ")
--> x <- 3:7
--> sum(x)
[1] 25
--> y <- log(x)
--> x - 100
[1] -97 -96 -95 -94 -93

or

> expr <- quote({ x <- 3:7 ; sum(x) ; y <- log(x) ; x - 100})
> source(auto.print=TRUE, exprs = expr, prompt="--> ")
--> x <- 3:7
--> sum(x)
[1] 25
--> y <- log(x)
--> x - 100
[1] -97 -96 -95 -94 -93

It was easy to implement, since exprs's default value is parse(file) or
parse(text=text), which source is calculating anyway.


Bill Dunlap
TIBCO Software
wdunlap tibco.com

On Fri, Sep 2, 2016 at 4:56 AM, Martin Maechler 
wrote:

> On R-help, with subject
>'[R] source() does not include added code'
>
> > Joshua Ulrich 
> > on Wed, 31 Aug 2016 10:35:01 -0500 writes:
>
> > I have quantstrat installed and it works fine for me.  If you're
> > asking why the output of t(tradeStats('macross')) isn't being
> printed,
> > that's because of what's described in the first paragraph in the
> > *Details* section of help("source"):
>
> > Note that running code via ‘source’ differs in a few respects from
> > entering it at the R command line.  Since expressions are not
> > executed at the top level, auto-printing is not done.  So you will
> > need to include explicit ‘print’ calls for things you want to be
> > printed (and remember that this includes plotting by ‘lattice’,
> > FAQ Q7.22).
>
>
>
> > So you need:
>
> > print(t(tradeStats('macross')))
>
> > if you want the output printed to the console.
>
> indeed, and "of course"" ;-)
>
> As my subject indicates, this is another case, where it would be
> very convenient to have a function
>
>withAutoprint()
>
> so the OP could have (hopefully) have used
>withAutoprint(source(..))
> though that would have been equivalent to the already nicely existing
>
>source(.., print.eval = TRUE)
>
> which works via the  withVisible(.) utility that returns for each
> 'expression' if it would auto print or not, and then does print (or
> not) accordingly.
>
> My own use cases for such a withAutoprint({...})
> are demos and examples, sometimes even package tests which I want to print:
>
> Assume I have a nice demo / example on a help page/ ...
>
> foo(..)
> (z <- bar(..))
> summary(z)
> 
>
> where I carefully do print parts (and don't others),
> and suddenly I find I want to run that part of the demo /
> example / test only in some circumstances, e.g., only when
> interactive, but not in BATCH, or only if it is me, the package maintainer,
>
> if( identical(Sys.getenv("USER"), "maechler") ) {
>   foo(..)
>   (z <- bar(..))
>   summary(z)
>   
> }
>
> Now all the auto-printing is gone, and
>
> 1) I have to find out which of these function calls do autoprint and wrap
>a print(..) around these, and
>
> 2) the result is quite ugly (for an example on a help page etc.)
>
> What I would like in a future R, is to be able to simply wrap the "{
> .. } above with an 'withAutoprint(.) :
>
> if( identical(Sys.getenv("USER"), "maechler") ) withAutoprint({
>   foo(..)
>   (z <- bar(..))
>   summary(z)
>   
> })
>
> Conceptually such a function could be written similar to source() with an R
> level for loop, treating each expression separately, calling eval(.) etc.
> That may cost too much performnace, ... still to have it would be better
> than
> not having the possibility.
>
> 
>
> If you read so far, you'd probably agree that such a function
> could be a nice asset in R,
> notably if it was possible to do this on the fast C level of R's main
> REPL.
>
> Have any of you looked into how this could be provided in R ?
> If you know the source a little, you will remember that there's
> the global variable  R_Visible  which is crucial here.
> The problem with that is that it *is* global, and only available
> as that; that the auto-printing "concept" is so linked to "toplevel
> context"
> and that is not easy, and AFAIK not so much centralized in one place in the
> source. Consequently, all kind of (very) low level functions manipulate
> R_Visible
> temporarily and so a C level implementation of  withAutoprint() may
> need considerable more changes than just setting R_Visible to TRUE in one
> place.
>
> Have any efforts / experiments already happened towards providing such
> functionality ?
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

[[alternative HTML version deleted]]

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

Re: [Rd] withAutoprint({ .... }) ?

2016-09-02 Thread Kirill Müller

On 02.09.2016 14:38, Duncan Murdoch wrote:

On 02/09/2016 7:56 AM, Martin Maechler wrote:

On R-help, with subject
   '[R] source() does not include added code'


Joshua Ulrich 
on Wed, 31 Aug 2016 10:35:01 -0500 writes:


> I have quantstrat installed and it works fine for me. If you're
> asking why the output of t(tradeStats('macross')) isn't being 
printed,

> that's because of what's described in the first paragraph in the
> *Details* section of help("source"):

> Note that running code via ‘source’ differs in a few respects from
> entering it at the R command line.  Since expressions are not
> executed at the top level, auto-printing is not done. So you will
> need to include explicit ‘print’ calls for things you want to be
> printed (and remember that this includes plotting by ‘lattice’,
> FAQ Q7.22).



> So you need:

> print(t(tradeStats('macross')))

> if you want the output printed to the console.

indeed, and "of course"" ;-)

As my subject indicates, this is another case, where it would be
very convenient to have a function

   withAutoprint()

so the OP could have (hopefully) have used
   withAutoprint(source(..))
though that would have been equivalent to the already nicely existing

   source(.., print.eval = TRUE)

which works via the  withVisible(.) utility that returns for each
'expression' if it would auto print or not, and then does print (or
not) accordingly.

My own use cases for such a withAutoprint({...})
are demos and examples, sometimes even package tests which I want to 
print:


Assume I have a nice demo / example on a help page/ ...

foo(..)
(z <- bar(..))
summary(z)


where I carefully do print parts (and don't others),
and suddenly I find I want to run that part of the demo /
example / test only in some circumstances, e.g., only when
interactive, but not in BATCH, or only if it is me, the package 
maintainer,


if( identical(Sys.getenv("USER"), "maechler") ) {
  foo(..)
  (z <- bar(..))
  summary(z)
  
}

Now all the auto-printing is gone, and

1) I have to find out which of these function calls do autoprint and 
wrap

   a print(..) around these, and

2) the result is quite ugly (for an example on a help page etc.)

What I would like in a future R, is to be able to simply wrap the "{
.. } above with an 'withAutoprint(.) :

if( identical(Sys.getenv("USER"), "maechler") ) withAutoprint({
  foo(..)
  (z <- bar(..))
  summary(z)
  
})

Conceptually such a function could be written similar to source() 
with an R
level for loop, treating each expression separately, calling eval(.) 
etc.
That may cost too much performnace, ... still to have it would be 
better than

not having the possibility.



If you read so far, you'd probably agree that such a function
could be a nice asset in R,
notably if it was possible to do this on the fast C level of R's main
REPL.

Have any of you looked into how this could be provided in R ?
If you know the source a little, you will remember that there's
the global variable  R_Visible  which is crucial here.
The problem with that is that it *is* global, and only available
as that; that the auto-printing "concept" is so linked to "toplevel 
context"
and that is not easy, and AFAIK not so much centralized in one place 
in the
source. Consequently, all kind of (very) low level functions 
manipulate R_Visible

temporarily and so a C level implementation of withAutoprint() may
need considerable more changes than just setting R_Visible to TRUE in 
one

place.

Have any efforts / experiments already happened towards providing such
functionality ?


I don't think the performance cost would matter.  If you're printing 
something, you're already slow.  So doing this at the R level would 
make most sense to me --- that's how Sweave and source and knitr do 
it, so it can't be that bad.


Duncan Murdoch

A C-level implementation would bring the benefit of a lean traceback() 
in case of an error. I suspect eval() could be enhanced to auto-print.


By the same token it would be extremely helpful to have a C-level 
implementation of local() which wouldn't litter the stack trace.



-Kirill

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

Re: [Rd] withAutoprint({ .... }) ?

2016-09-02 Thread Duncan Murdoch

On 02/09/2016 7:56 AM, Martin Maechler wrote:

On R-help, with subject
   '[R] source() does not include added code'


Joshua Ulrich 
on Wed, 31 Aug 2016 10:35:01 -0500 writes:


> I have quantstrat installed and it works fine for me.  If you're
> asking why the output of t(tradeStats('macross')) isn't being printed,
> that's because of what's described in the first paragraph in the
> *Details* section of help("source"):

> Note that running code via ‘source’ differs in a few respects from
> entering it at the R command line.  Since expressions are not
> executed at the top level, auto-printing is not done.  So you will
> need to include explicit ‘print’ calls for things you want to be
> printed (and remember that this includes plotting by ‘lattice’,
> FAQ Q7.22).



> So you need:

> print(t(tradeStats('macross')))

> if you want the output printed to the console.

indeed, and "of course"" ;-)

As my subject indicates, this is another case, where it would be
very convenient to have a function

   withAutoprint()

so the OP could have (hopefully) have used
   withAutoprint(source(..))
though that would have been equivalent to the already nicely existing

   source(.., print.eval = TRUE)

which works via the  withVisible(.) utility that returns for each
'expression' if it would auto print or not, and then does print (or
not) accordingly.

My own use cases for such a withAutoprint({...})
are demos and examples, sometimes even package tests which I want to print:

Assume I have a nice demo / example on a help page/ ...

foo(..)
(z <- bar(..))
summary(z)


where I carefully do print parts (and don't others),
and suddenly I find I want to run that part of the demo /
example / test only in some circumstances, e.g., only when
interactive, but not in BATCH, or only if it is me, the package maintainer,

if( identical(Sys.getenv("USER"), "maechler") ) {
  foo(..)
  (z <- bar(..))
  summary(z)
  
}

Now all the auto-printing is gone, and

1) I have to find out which of these function calls do autoprint and wrap
   a print(..) around these, and

2) the result is quite ugly (for an example on a help page etc.)

What I would like in a future R, is to be able to simply wrap the "{
.. } above with an 'withAutoprint(.) :

if( identical(Sys.getenv("USER"), "maechler") ) withAutoprint({
  foo(..)
  (z <- bar(..))
  summary(z)
  
})

Conceptually such a function could be written similar to source() with an R
level for loop, treating each expression separately, calling eval(.) etc.
That may cost too much performnace, ... still to have it would be better than
not having the possibility.



If you read so far, you'd probably agree that such a function
could be a nice asset in R,
notably if it was possible to do this on the fast C level of R's main
REPL.

Have any of you looked into how this could be provided in R ?
If you know the source a little, you will remember that there's
the global variable  R_Visible  which is crucial here.
The problem with that is that it *is* global, and only available
as that; that the auto-printing "concept" is so linked to "toplevel context"
and that is not easy, and AFAIK not so much centralized in one place in the
source. Consequently, all kind of (very) low level functions manipulate 
R_Visible
temporarily and so a C level implementation of  withAutoprint() may
need considerable more changes than just setting R_Visible to TRUE in one
place.

Have any efforts / experiments already happened towards providing such
functionality ?


I don't think the performance cost would matter.  If you're printing 
something, you're already slow.  So doing this at the R level would make 
most sense to me --- that's how Sweave and source and knitr do it, so it 
can't be that bad.


Duncan Murdoch

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

[Rd] withAutoprint({ .... }) ?

2016-09-02 Thread Martin Maechler
On R-help, with subject
   '[R] source() does not include added code'

> Joshua Ulrich 
> on Wed, 31 Aug 2016 10:35:01 -0500 writes:

> I have quantstrat installed and it works fine for me.  If you're
> asking why the output of t(tradeStats('macross')) isn't being printed,
> that's because of what's described in the first paragraph in the
> *Details* section of help("source"):

> Note that running code via ‘source’ differs in a few respects from
> entering it at the R command line.  Since expressions are not
> executed at the top level, auto-printing is not done.  So you will
> need to include explicit ‘print’ calls for things you want to be
> printed (and remember that this includes plotting by ‘lattice’,
> FAQ Q7.22).



> So you need:

> print(t(tradeStats('macross')))

> if you want the output printed to the console.

indeed, and "of course"" ;-)

As my subject indicates, this is another case, where it would be
very convenient to have a function

   withAutoprint()

so the OP could have (hopefully) have used
   withAutoprint(source(..))
though that would have been equivalent to the already nicely existing

   source(.., print.eval = TRUE)

which works via the  withVisible(.) utility that returns for each
'expression' if it would auto print or not, and then does print (or
not) accordingly.

My own use cases for such a withAutoprint({...})
are demos and examples, sometimes even package tests which I want to print:

Assume I have a nice demo / example on a help page/ ...

foo(..)
(z <- bar(..))
summary(z)


where I carefully do print parts (and don't others),
and suddenly I find I want to run that part of the demo /
example / test only in some circumstances, e.g., only when
interactive, but not in BATCH, or only if it is me, the package maintainer,

if( identical(Sys.getenv("USER"), "maechler") ) {
  foo(..)
  (z <- bar(..))
  summary(z)
  
}

Now all the auto-printing is gone, and

1) I have to find out which of these function calls do autoprint and wrap
   a print(..) around these, and

2) the result is quite ugly (for an example on a help page etc.)

What I would like in a future R, is to be able to simply wrap the "{
.. } above with an 'withAutoprint(.) :

if( identical(Sys.getenv("USER"), "maechler") ) withAutoprint({
  foo(..)
  (z <- bar(..))
  summary(z)
  
})

Conceptually such a function could be written similar to source() with an R
level for loop, treating each expression separately, calling eval(.) etc.
That may cost too much performnace, ... still to have it would be better than
not having the possibility.



If you read so far, you'd probably agree that such a function
could be a nice asset in R,
notably if it was possible to do this on the fast C level of R's main
REPL.

Have any of you looked into how this could be provided in R ?
If you know the source a little, you will remember that there's
the global variable  R_Visible  which is crucial here.
The problem with that is that it *is* global, and only available
as that; that the auto-printing "concept" is so linked to "toplevel context"
and that is not easy, and AFAIK not so much centralized in one place in the
source. Consequently, all kind of (very) low level functions manipulate 
R_Visible
temporarily and so a C level implementation of  withAutoprint() may
need considerable more changes than just setting R_Visible to TRUE in one
place. 

Have any efforts / experiments already happened towards providing such
functionality ?

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