From dcc9a17e2c3db190072d8c5ab24740c1d0d5ed7a Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 11:36:27 -0500 Subject: [PATCH 01/18] Putting bgCol in background --- R/bgCol.R | 22 ++++++++++++++++------ R/calc_views.R | 7 ++++++- R/print.R | 13 +++++++++++-- inst/extdata/default.yaml | 3 ++- man/bgCol.Rd | 7 ++++++- 5 files changed, 41 insertions(+), 11 deletions(-) diff --git a/R/bgCol.R b/R/bgCol.R index 4038272..09f0960 100644 --- a/R/bgCol.R +++ b/R/bgCol.R @@ -10,23 +10,33 @@ #' @examples #' gs <- gsplot() %>% #' points(y=c(3,1,2), x=4:6, xlim=c(0,NA),legend.name="Points") %>% +#' bgCol(col="lightgrey") %>% #' lines( c(3,4,3), c(2,4,6), legend.name="Lines", side=c(3,4)) %>% -#' legend(location="topleft") %>% -#' bgCol(col="lightgrey") -#' +#' legend(location="topleft") #' gs #' -#' gsPlain <- gsplot()%>% +#' gsPlain <- gsplot() %>% #' points(1:100, rnorm(100,mean=10000, sd=1000), log="y") %>% #' bgCol(col="lightgrey") #' gsPlain +#' +#' gsPlain <- gsplot() %>% +#' points(1:100, rnorm(100,mean=10000, sd=1000), log="y") %>% +#' bgCol() #yaml specifies lightgrey +#' gsPlain bgCol <- function(object, ...) { override("gsplot", "bgCol", object, ...) } -bgCol.gsplot <- function(object, ..., side=c(1,2)){ - set_window_args(object, fun.name="bgCol", ..., legend.name=NULL, side=side, package='gsplot') +bgCol.gsplot <- function(object, ...){ + + to.gsplot <- set_args("bgCol",..., package = "gsplot") + + to.gsplot <- list("bgCol"=to.gsplot) + + object <- append(object, to.gsplot) + return(gsplot(object)) } bgCol.default <- function(col,...){ diff --git a/R/calc_views.R b/R/calc_views.R index 83f2171..a7edde1 100644 --- a/R/calc_views.R +++ b/R/calc_views.R @@ -38,7 +38,11 @@ group_views <- function(gsplot){ gsplot[[length(gsplot)]] <- NULL views <- views(gsplot) # existing non.views <- non_views(gsplot) - add_sides <- set_sides(tail.gs[['gs.config']][['side']]) + add_sides <- NULL + + if(is.list(tail.gs)){ + add_sides <- set_sides(tail.gs[['gs.config']][['side']]) + } if (!is.null(add_sides)){ to_draw <- setNames(list(c(tail.gs[['arguments']], legend.name=tail.gs[['gs.config']][['legend.name']])), tail.nm) @@ -186,6 +190,7 @@ c_unname <- function(list){ unname_c <- function(list){ do.call(c, unname(list)) } + views_with_side <- function(views, side){ if(length(side) > 1) stop('side can only be length of 1') diff --git a/R/print.R b/R/print.R index 13e3c67..02dfdea 100644 --- a/R/print.R +++ b/R/print.R @@ -43,10 +43,13 @@ print.gsplot <- function(x, ...){ i <- which(names(views) %in% 'axis') definded.sides <- sapply(i, function(x) views[[x]][['arguments']][['side']]) + bg.arg <- views$bgCol + grid.arg <- views$grid + view.info <- view_info(views) view.sides.drawn <- NULL - - for (i in which(names(views) %in% 'view')){ + view.index <- which(names(views) %in% 'view') + for (i in view.index){ plots = views[[i]] plots[['window']] <- NULL @@ -57,6 +60,12 @@ print.gsplot <- function(x, ...){ par(window[['par']]) plot.window(xlim = window$xlim, ylim = window$ylim, log = view.info$log[i==view.info$index]) + # -- initial view -- + if(i == view.index[1]){ + bgCol(bg.arg) + #draw_grid(grid.arg) + } + sides.not.defined <- window$side[!(window$side %in% definded.sides)] if(!is.null(view.sides.drawn)){ diff --git a/inst/extdata/default.yaml b/inst/extdata/default.yaml index 1f44dec..f03b68e 100644 --- a/inst/extdata/default.yaml +++ b/inst/extdata/default.yaml @@ -39,6 +39,7 @@ error_bar: arrows: NULL callouts: col: 'black' -bgCol: NULL +bgCol: + col: 'lightgrey' orderToPlot: order: [grid, bgCol] diff --git a/man/bgCol.Rd b/man/bgCol.Rd index 773e344..449a982 100644 --- a/man/bgCol.Rd +++ b/man/bgCol.Rd @@ -23,9 +23,14 @@ gs <- gsplot() \%>\% gs -gsPlain <- gsplot()\%>\% +gsPlain <- gsplot() \%>\% points(1:100, rnorm(100,mean=10000, sd=1000), log="y") \%>\% bgCol(col="lightgrey") gsPlain + +gsPlain <- gsplot() \%>\% + points(1:100, rnorm(100,mean=10000, sd=1000), log="y") \%>\% + bgCol() #yaml specifies lightgrey +gsPlain } From 0c7a15bc5bf7b1daa376c795a2c405b5f0eb5808 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 11:47:55 -0500 Subject: [PATCH 02/18] Fixes #250 --- R/axis.R | 1 + R/bgCol.R | 13 +++++++++---- man/axis.Rd | 1 + man/bgCol.Rd | 18 +++++++++++------- tests/testthat/tests-bgCol.R | 2 +- 5 files changed, 23 insertions(+), 12 deletions(-) diff --git a/R/axis.R b/R/axis.R index b6a4967..41ef200 100644 --- a/R/axis.R +++ b/R/axis.R @@ -17,6 +17,7 @@ #' gs <- gsplot() %>% #' points(x=1:5, y=1:5, legend.name="Stuff") %>% #' lines(2:6, y=2:6, ylim=c(0,10)) %>% +#' bgCol(col="lightgoldenrod") %>% #' axis(side=c(3,4),labels=FALSE) %>% #' legend("topright") #' gs diff --git a/R/bgCol.R b/R/bgCol.R index 09f0960..411d4bd 100644 --- a/R/bgCol.R +++ b/R/bgCol.R @@ -15,15 +15,20 @@ #' legend(location="topleft") #' gs #' -#' gsPlain <- gsplot() %>% +#' gs <- gsplot() %>% #' points(1:100, rnorm(100,mean=10000, sd=1000), log="y") %>% #' bgCol(col="lightgrey") -#' gsPlain +#' gs #' -#' gsPlain <- gsplot() %>% +#' gs <- gsplot() %>% #' points(1:100, rnorm(100,mean=10000, sd=1000), log="y") %>% #' bgCol() #yaml specifies lightgrey -#' gsPlain +#' gs +#' +#' gs <- gsplot() %>% +#' points(1:100, rnorm(100,mean=10000, sd=1000), log="y") %>% +#' bgCol("lightgoldenrod") +#' gs bgCol <- function(object, ...) { override("gsplot", "bgCol", object, ...) } diff --git a/man/axis.Rd b/man/axis.Rd index 8c6cbc3..faac4ee 100644 --- a/man/axis.Rd +++ b/man/axis.Rd @@ -25,6 +25,7 @@ Additional graphical parameter inputs: gs <- gsplot() \%>\% points(x=1:5, y=1:5, legend.name="Stuff") \%>\% lines(2:6, y=2:6, ylim=c(0,10)) \%>\% + bgCol(col="lightgoldenrod") \%>\% axis(side=c(3,4),labels=FALSE) \%>\% legend("topright") gs diff --git a/man/bgCol.Rd b/man/bgCol.Rd index 449a982..b1147f4 100644 --- a/man/bgCol.Rd +++ b/man/bgCol.Rd @@ -17,20 +17,24 @@ Adds color to the plot background. \examples{ gs <- gsplot() \%>\% points(y=c(3,1,2), x=4:6, xlim=c(0,NA),legend.name="Points") \%>\% + bgCol(col="lightgrey") \%>\% lines( c(3,4,3), c(2,4,6), legend.name="Lines", side=c(3,4)) \%>\% - legend(location="topleft") \%>\% - bgCol(col="lightgrey") - + legend(location="topleft") gs -gsPlain <- gsplot() \%>\% +gs <- gsplot() \%>\% points(1:100, rnorm(100,mean=10000, sd=1000), log="y") \%>\% bgCol(col="lightgrey") -gsPlain +gs -gsPlain <- gsplot() \%>\% +gs <- gsplot() \%>\% points(1:100, rnorm(100,mean=10000, sd=1000), log="y") \%>\% bgCol() #yaml specifies lightgrey -gsPlain +gs + +gs <- gsplot() \%>\% + points(1:100, rnorm(100,mean=10000, sd=1000), log="y") \%>\% + bgCol("lightgoldenrod") +gs } diff --git a/tests/testthat/tests-bgCol.R b/tests/testthat/tests-bgCol.R index f1119f8..475ca5e 100644 --- a/tests/testthat/tests-bgCol.R +++ b/tests/testthat/tests-bgCol.R @@ -10,7 +10,7 @@ test_that("testing content of gsplot list for bgCol", { points(1:10, col="black") %>% bgCol(col="coral2") - expect_true(any(names(gs[['view']]) %in% "bgCol")) + expect_true(any(names(gs) %in% "bgCol")) }) From ad096fab194aff215eab82271f0921a405acec9b Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 11:53:36 -0500 Subject: [PATCH 03/18] Moving drawing of axis to after views, but before legend. I think it looks better. --- R/print.R | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/R/print.R b/R/print.R index 02dfdea..5f14050 100644 --- a/R/print.R +++ b/R/print.R @@ -44,6 +44,7 @@ print.gsplot <- function(x, ...){ definded.sides <- sapply(i, function(x) views[[x]][['arguments']][['side']]) bg.arg <- views$bgCol + title.arg <- views$title grid.arg <- views$grid view.info <- view_info(views) @@ -63,6 +64,7 @@ print.gsplot <- function(x, ...){ # -- initial view -- if(i == view.index[1]){ bgCol(bg.arg) + title(title.arg) #draw_grid(grid.arg) } @@ -72,6 +74,9 @@ print.gsplot <- function(x, ...){ view.sides.drawn <- sides.not.defined[-view.sides.drawn] } + # -- call functions -- + to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) + if(window$axes){ for(j in sides.not.defined){ if(j %% 2 != 0){ @@ -88,9 +93,6 @@ print.gsplot <- function(x, ...){ mtext(text=window$ylab, side=window$side[2], line = 2) } - # -- call functions -- - to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) - par(new=TRUE) } From fbdccd204c08fc897da3f5c221ed3e1972a63500 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 11:54:31 -0500 Subject: [PATCH 04/18] Title to top level. --- R/title.R | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/R/title.R b/R/title.R index 45fb374..1de8f81 100644 --- a/R/title.R +++ b/R/title.R @@ -29,5 +29,11 @@ title <- function(object, ...) { title.gsplot <- function(object, ..., legend.name=NULL, side=c(1,2)){ - set_window_args(object, fun.name='title', ..., legend.name=legend.name, side=side, def.funs=graphics::title) + to.gsplot <- set_args("title",..., package = "graphics") + + to.gsplot <- list("title"=to.gsplot) + + object <- append(object, to.gsplot) + return(gsplot(object)) + # set_window_args(object, fun.name='title', ..., legend.name=legend.name, side=side, def.funs=graphics::title) } \ No newline at end of file From f5975bfd73e6bd2164bb7347cb9cb9636a7d5984 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 12:18:13 -0500 Subject: [PATCH 05/18] Changing default las to 1, adding title test. --- R/axis.R | 6 +++--- inst/extdata/default.yaml | 4 ++-- man/axis.Rd | 6 +++--- tests/testthat/test-title.R | 17 +++++++++++++++++ tests/testthat/tests-bgCol.R | 3 ++- 5 files changed, 27 insertions(+), 9 deletions(-) create mode 100644 tests/testthat/test-title.R diff --git a/R/axis.R b/R/axis.R index 41ef200..57e7937 100644 --- a/R/axis.R +++ b/R/axis.R @@ -23,7 +23,7 @@ #' gs #' #' gs <- gsplot() %>% -#' points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA)) %>% +#' points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA),las=0) %>% #' axis(side=c(4), labels=FALSE) %>% #' axis(side=c(1,3), n.minor=4) #' gs @@ -35,8 +35,8 @@ #' gs #' #' gs <- gsplot() %>% -#' points(1:5, c(1,10,100,1000,10000), log="y", las=1) %>% -#' axis(side=c(2,4), n.minor=4) +#' points(1:5, c(1,10,100,1000,10000), log="y") %>% +#' axis(side=c(2,4), n.minor=4, las=1) #' gs #' #' gs <- gsplot() %>% diff --git a/inst/extdata/default.yaml b/inst/extdata/default.yaml index f03b68e..f9a7c0c 100644 --- a/inst/extdata/default.yaml +++ b/inst/extdata/default.yaml @@ -4,6 +4,7 @@ tcl: 0.3 mgp: [1.5, 0.3, 0.0] yaxt: "s" xaxt: "s" +las: 1 points: pch: 6 col: "red" @@ -41,5 +42,4 @@ callouts: col: 'black' bgCol: col: 'lightgrey' -orderToPlot: - order: [grid, bgCol] + diff --git a/man/axis.Rd b/man/axis.Rd index faac4ee..92e34d1 100644 --- a/man/axis.Rd +++ b/man/axis.Rd @@ -31,7 +31,7 @@ gs <- gsplot() \%>\% gs gs <- gsplot() \%>\% - points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA)) \%>\% + points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA),las=0) \%>\% axis(side=c(4), labels=FALSE) \%>\% axis(side=c(1,3), n.minor=4) gs @@ -43,8 +43,8 @@ gs <- gsplot() \%>\% gs gs <- gsplot() \%>\% - points(1:5, c(1,10,100,1000,10000), log="y", las=1) \%>\% - axis(side=c(2,4), n.minor=4) + points(1:5, c(1,10,100,1000,10000), log="y") \%>\% + axis(side=c(2,4), n.minor=4, las=1) gs gs <- gsplot() \%>\% diff --git a/tests/testthat/test-title.R b/tests/testthat/test-title.R new file mode 100644 index 0000000..c3b267d --- /dev/null +++ b/tests/testthat/test-title.R @@ -0,0 +1,17 @@ +context("title") + +test_that("testing content of gsplot list for title", { + + gs <- gsplot(list()) + + expect_is(gs,"gsplot") + + gs <- gsplot() %>% + points(1:10, 1:10) %>% + lines(20:30,20:30, side=c(3,4)) %>% + title("Great Graph") + + expect_true(any(names(gs) %in% "bgCol")) + +}) + diff --git a/tests/testthat/tests-bgCol.R b/tests/testthat/tests-bgCol.R index 475ca5e..ec86b1d 100644 --- a/tests/testthat/tests-bgCol.R +++ b/tests/testthat/tests-bgCol.R @@ -7,7 +7,8 @@ test_that("testing content of gsplot list for bgCol", { expect_is(gs,"gsplot") gs <- gsplot() %>% - points(1:10, col="black") %>% + points(1:10, 1:10) %>% + lines(20:30,20:30, side=c(3,4)) %>% bgCol(col="coral2") expect_true(any(names(gs) %in% "bgCol")) From 1fc4fef8c738e334048d1a64ea041414649c3cbe Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 12:46:50 -0500 Subject: [PATCH 06/18] Changed default to always horizontal numbers, but vertical y label. --- R/print.R | 5 +++-- R/title.R | 18 +++++++++++------- inst/extdata/default.yaml | 3 ++- man/title.Rd | 18 +++++++++++------- 4 files changed, 27 insertions(+), 17 deletions(-) diff --git a/R/print.R b/R/print.R index 5f14050..12a9684 100644 --- a/R/print.R +++ b/R/print.R @@ -50,6 +50,7 @@ print.gsplot <- function(x, ...){ view.info <- view_info(views) view.sides.drawn <- NULL view.index <- which(names(views) %in% 'view') + for (i in view.index){ plots = views[[i]] @@ -89,8 +90,8 @@ print.gsplot <- function(x, ...){ } if(window$ann){ - mtext(text=window$xlab, side=window$side[1], line = 2) - mtext(text=window$ylab, side=window$side[2], line = 2) + mtext(text=window$xlab, side=window$side[1], line = 2, las=config("mtext")$las) + mtext(text=window$ylab, side=window$side[2], line = 2, las=config("mtext")$las) } par(new=TRUE) diff --git a/R/title.R b/R/title.R index 1de8f81..55a6c37 100644 --- a/R/title.R +++ b/R/title.R @@ -16,13 +16,17 @@ #' #' @export #' @examples -#' gs <- gsplot() -#' gsNew <- points(gs, y=1, x=2, col="blue", pch=18, legend.name="Points", xlab="Stuff") -#' gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data!") -#' gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") -#' gsNew <- legend(gsNew, location="topleft",title="Awesome!") -#' gsNew <- title(gsNew, main="Great Graph", col.main="grey", font.main=2, cex.main=2) -#' gsNew +#' gs <- gsplot() %>% +#' points(y=1, x=2, col="blue", pch=18, legend.name="Points", xlab="Stuff") %>% +#' lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data!") %>% +#' abline(b=1, a=0, legend.name="1:1") %>% +#' legend(location="topleft",title="Awesome!") %>% +#' title(main="Great Graph", col.main="grey", font.main=2, cex.main=2) +#' gs +#' gs <- gsplot() %>% +#' points(y=1, x=2) %>% +#' title(main="Great Graph") +#' gs title <- function(object, ...) { override("graphics", "title", object, ...) } diff --git a/inst/extdata/default.yaml b/inst/extdata/default.yaml index f9a7c0c..254ba0e 100644 --- a/inst/extdata/default.yaml +++ b/inst/extdata/default.yaml @@ -25,7 +25,8 @@ axis: outer: FALSE title: NULL text: NULL -mtext: NULL +mtext: + las: 0 grid: col: "grey" lwd: 1 diff --git a/man/title.Rd b/man/title.Rd index c45579f..20847b7 100644 --- a/man/title.Rd +++ b/man/title.Rd @@ -25,12 +25,16 @@ Additional graphical parameter inputs: } } \examples{ -gs <- gsplot() -gsNew <- points(gs, y=1, x=2, col="blue", pch=18, legend.name="Points", xlab="Stuff") -gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data!") -gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") -gsNew <- legend(gsNew, location="topleft",title="Awesome!") -gsNew <- title(gsNew, main="Great Graph", col.main="grey", font.main=2, cex.main=2) -gsNew +gs <- gsplot() \%>\% + points(y=1, x=2, col="blue", pch=18, legend.name="Points", xlab="Stuff") \%>\% + lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data!") \%>\% + abline(b=1, a=0, legend.name="1:1") \%>\% + legend(location="topleft",title="Awesome!") \%>\% + title(main="Great Graph", col.main="grey", font.main=2, cex.main=2) +gs +gs <- gsplot() \%>\% + points(y=1, x=2) \%>\% + title(main="Great Graph") +gs } From 844fb9d97eee6685fae62d2258bfc59821f4d4eb Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 13:05:53 -0500 Subject: [PATCH 07/18] Actually, pretty happy with grid. --- R/grid.R | 12 ++++++++++-- R/print.R | 4 +--- man/grid.Rd | 5 +++++ 3 files changed, 16 insertions(+), 5 deletions(-) diff --git a/R/grid.R b/R/grid.R index ed15051..0b610f4 100644 --- a/R/grid.R +++ b/R/grid.R @@ -15,11 +15,19 @@ #' gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") #' gsNew <- legend(gsNew, location="topleft",title="Awesome!") #' gsNew +#' +#' gs <- gsplot() %>% +#' points(1:10,1:10) %>% +#' lines(6:14,6:14,side=c(3,4)) +#' gs +#' grid <- function(object, ...) { override("graphics", "grid", object, ...) } - grid.gsplot <- function(object, ..., legend.name=NULL, side=c(1,2)){ - set_window_args(object, fun.name='grid', ..., legend.name=legend.name, side=side, def.funs = graphics::grid) + + object <- set_window_args(object, fun.name='grid', ..., legend.name=legend.name, side=side, def.funs = graphics::grid) + + } \ No newline at end of file diff --git a/R/print.R b/R/print.R index 12a9684..d0499a6 100644 --- a/R/print.R +++ b/R/print.R @@ -45,7 +45,6 @@ print.gsplot <- function(x, ...){ bg.arg <- views$bgCol title.arg <- views$title - grid.arg <- views$grid view.info <- view_info(views) view.sides.drawn <- NULL @@ -66,9 +65,8 @@ print.gsplot <- function(x, ...){ if(i == view.index[1]){ bgCol(bg.arg) title(title.arg) - #draw_grid(grid.arg) } - + sides.not.defined <- window$side[!(window$side %in% definded.sides)] if(!is.null(view.sides.drawn)){ diff --git a/man/grid.Rd b/man/grid.Rd index b054890..c29c853 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -23,5 +23,10 @@ gsNew <- grid(gsNew) gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") gsNew <- legend(gsNew, location="topleft",title="Awesome!") gsNew + +gs <- gsplot() \%>\% + points(1:10,1:10) \%>\% + lines(6:14,6:14,side=c(3,4)) +gs } From 509edd60743db78d3e3816dfe47661559b21d49b Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 13:07:26 -0500 Subject: [PATCH 08/18] Fixes #239 --- R/grid.R | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/R/grid.R b/R/grid.R index 0b610f4..ace1734 100644 --- a/R/grid.R +++ b/R/grid.R @@ -18,7 +18,8 @@ #' #' gs <- gsplot() %>% #' points(1:10,1:10) %>% -#' lines(6:14,6:14,side=c(3,4)) +#' lines(6:14,6:14,side=c(3,4)) %>% +#' grid(side=c(3,4)) #' gs #' grid <- function(object, ...) { From a9088f056b3ce8623a9b4b4ff8b7619a25050134 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 13:09:12 -0500 Subject: [PATCH 09/18] Fixing test. --- man/grid.Rd | 3 ++- tests/testthat/test-title.R | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/man/grid.Rd b/man/grid.Rd index c29c853..a6cddce 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -26,7 +26,8 @@ gsNew gs <- gsplot() \%>\% points(1:10,1:10) \%>\% - lines(6:14,6:14,side=c(3,4)) + lines(6:14,6:14,side=c(3,4)) \%>\% + grid(side=c(3,4)) gs } diff --git a/tests/testthat/test-title.R b/tests/testthat/test-title.R index c3b267d..a942cdc 100644 --- a/tests/testthat/test-title.R +++ b/tests/testthat/test-title.R @@ -11,7 +11,7 @@ test_that("testing content of gsplot list for title", { lines(20:30,20:30, side=c(3,4)) %>% title("Great Graph") - expect_true(any(names(gs) %in% "bgCol")) + expect_true(any(names(gs) %in% "title")) }) From 911abcb4bd028676317f684208496cc2bd28f4b5 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 13:54:54 -0500 Subject: [PATCH 10/18] Cleaned up axis logic. --- R/access-gsplot.R | 7 +++++++ R/grid.R | 8 ++++++-- R/print.R | 21 ++++++--------------- man/grid.Rd | 8 +++++++- 4 files changed, 26 insertions(+), 18 deletions(-) diff --git a/R/access-gsplot.R b/R/access-gsplot.R index 4e356c3..45e13c0 100644 --- a/R/access-gsplot.R +++ b/R/access-gsplot.R @@ -95,5 +95,12 @@ view_info <- function(object){ viewInfo[,c("x","y","index")] <- sapply(viewInfo[,c("x","y","index")], function(x) as.integer(x)) + i <- which(names(object) %in% 'axis') + definded.sides <- sapply(i, function(x) object[[x]][['arguments']][['side']]) + view.sides.drawn <- NULL + + viewInfo$x.side.defined.by.user <- viewInfo$x %in% definded.sides + viewInfo$y.side.defined.by.user <- viewInfo$y %in% definded.sides + return(viewInfo) } \ No newline at end of file diff --git a/R/grid.R b/R/grid.R index ace1734..aadc2a6 100644 --- a/R/grid.R +++ b/R/grid.R @@ -11,7 +11,7 @@ #' gsNew <- points(gs, y=1, x=2, xlim=c(0,NA),ylim=c(0,NA), #' col="blue", pch=18, legend.name="Points") #' gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines") -#' gsNew <- grid(gsNew) +#' gsNew <- grid(gsNew, legend.name="Grid") #' gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") #' gsNew <- legend(gsNew, location="topleft",title="Awesome!") #' gsNew @@ -22,6 +22,11 @@ #' grid(side=c(3,4)) #' gs #' +#' gs <- gsplot() %>% +#' points(1:10,1:10) %>% +#' axis(side=1, at=seq(1,10,length.out=18)) %>% +#' grid() +#' gs grid <- function(object, ...) { override("graphics", "grid", object, ...) } @@ -30,5 +35,4 @@ grid.gsplot <- function(object, ..., legend.name=NULL, side=c(1,2)){ object <- set_window_args(object, fun.name='grid', ..., legend.name=legend.name, side=side, def.funs = graphics::grid) - } \ No newline at end of file diff --git a/R/print.R b/R/print.R index d0499a6..05f48a7 100644 --- a/R/print.R +++ b/R/print.R @@ -47,8 +47,7 @@ print.gsplot <- function(x, ...){ title.arg <- views$title view.info <- view_info(views) - view.sides.drawn <- NULL - view.index <- which(names(views) %in% 'view') + view.index <- view.info$index for (i in view.index){ @@ -67,23 +66,15 @@ print.gsplot <- function(x, ...){ title(title.arg) } - sides.not.defined <- window$side[!(window$side %in% definded.sides)] - - if(!is.null(view.sides.drawn)){ - view.sides.drawn <- sides.not.defined[-view.sides.drawn] - } - # -- call functions -- to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) if(window$axes){ - for(j in sides.not.defined){ - if(j %% 2 != 0){ - Axis(side=j,x=window$xlim) - } else { - Axis(side=j,x=window$ylim) - } - view.sides.drawn <- append(view.sides.drawn, j) + if(!view.info$x.side.defined.by.user[i]){ + Axis(side=view.info$x[i],x=window$xlim) + } + if(!view.info$y.side.defined.by.user[i]){ + Axis(side=view.info$y[i],x=window$ylim) } } diff --git a/man/grid.Rd b/man/grid.Rd index a6cddce..2bd2947 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -19,7 +19,7 @@ gs <- gsplot() gsNew <- points(gs, y=1, x=2, xlim=c(0,NA),ylim=c(0,NA), col="blue", pch=18, legend.name="Points") gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines") -gsNew <- grid(gsNew) +gsNew <- grid(gsNew, legend.name="Grid") gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") gsNew <- legend(gsNew, location="topleft",title="Awesome!") gsNew @@ -29,5 +29,11 @@ gs <- gsplot() \%>\% lines(6:14,6:14,side=c(3,4)) \%>\% grid(side=c(3,4)) gs + +gs <- gsplot() \%>\% + points(1:10,1:10) \%>\% + axis(side=1, at=seq(1,10,length.out=18)) \%>\% + grid() +gs } From c1f92dace834dbcb34d292692935eb6cd7e5235a Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 15:32:52 -0500 Subject: [PATCH 11/18] Fixes #100 --- R/grid.R | 40 ++++++++++++++++++++++++++++++++++++++-- R/print.R | 12 ++++++++++-- man/grid.Rd | 6 ++++-- 3 files changed, 52 insertions(+), 6 deletions(-) diff --git a/R/grid.R b/R/grid.R index aadc2a6..cc39724 100644 --- a/R/grid.R +++ b/R/grid.R @@ -24,8 +24,10 @@ #' #' gs <- gsplot() %>% #' points(1:10,1:10) %>% -#' axis(side=1, at=seq(1,10,length.out=18)) %>% -#' grid() +#' axis(side=1, at=seq(1,10,length.out=18),las=3) %>% +#' axis(side=3, labels=FALSE) %>% +#' grid(side=c(1,2),col="green") %>% +#' grid(side=c(3,4)) #' gs grid <- function(object, ...) { override("graphics", "grid", object, ...) @@ -35,4 +37,38 @@ grid.gsplot <- function(object, ..., legend.name=NULL, side=c(1,2)){ object <- set_window_args(object, fun.name='grid', ..., legend.name=legend.name, side=side, def.funs = graphics::grid) +} + +draw_custom_grid <- function(object, index){ + + i <- which(names(object) %in% 'axis') + definded.sides <- sapply(i, function(x) object[[x]][['arguments']][['side']]) + + view.info <- view_info(object) + view.info <- view.info[index == view.info$index,] + + grid.args <- set_args("grid",object[[index]][['grid']], package = "graphics") + + if(view.info$x.side.defined.by.user){ + axes.index <- i[definded.sides == view.info$x] + x.at <- object[axes.index][['axis']][['arguments']][['at']] + if(length(x.at) == 0){ + x.at <- axTicks(view.info$x) + } + } else { + x.at <- axTicks(view.info$x) + } + + if(view.info$y.side.defined.by.user){ + axes.index <- i[definded.sides == view.info$y] + y.at <- object[axes.index][['axis']][['arguments']][['at']] + if(length(y.at) == 0){ + y.at <- axTicks(view.info$y) + } + } else { + y.at <- axTicks(view.info$y) + } + + abline(h=y.at, v=x.at, grid.args) + } \ No newline at end of file diff --git a/R/print.R b/R/print.R index 05f48a7..d512a84 100644 --- a/R/print.R +++ b/R/print.R @@ -65,10 +65,18 @@ print.gsplot <- function(x, ...){ bgCol(bg.arg) title(title.arg) } - + # -- call functions -- - to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) + if(sum(view.info$x.side.defined.by.user[i], view.info$y.side.defined.by.user[i])== 0 | + !(any(names(plots) %in% 'grid'))){ + to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) + } else { + draw_custom_grid(views,i) + plots <- plots[!(names(plots) %in% 'grid')] + to_gsplot(lapply(plots, function(x) x[!(names(x) %in% c('legend.name'))])) + } + if(window$axes){ if(!view.info$x.side.defined.by.user[i]){ Axis(side=view.info$x[i],x=window$xlim) diff --git a/man/grid.Rd b/man/grid.Rd index 2bd2947..94c3758 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -32,8 +32,10 @@ gs gs <- gsplot() \%>\% points(1:10,1:10) \%>\% - axis(side=1, at=seq(1,10,length.out=18)) \%>\% - grid() + axis(side=1, at=seq(1,10,length.out=18),las=3) \%>\% + axis(side=3, labels=FALSE) \%>\% + grid(side=c(1,2),col="green") \%>\% + grid(side=c(3,4)) gs } From 794c05e52c5932cf816819fdeaf3cf24c2570e93 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 16:30:06 -0500 Subject: [PATCH 12/18] Fixes #100 Allows dates/posixct in grid. --- R/grid.R | 36 ++++++++++++------ R/print.R | 3 +- README.Rmd | 11 +++--- README.md | 11 +++--- .../unnamed-chunk-2-1.png | Bin 6917 -> 8467 bytes .../unnamed-chunk-3-1.png | Bin 5180 -> 5243 bytes .../unnamed-chunk-4-1.png | Bin 8330 -> 7791 bytes inst/doc/gsplotIntro.R | 13 ++++--- inst/doc/gsplotIntro.Rmd | 13 ++++--- inst/doc/gsplotIntro.html | 32 ++++++++-------- vignettes/gsplotIntro.Rmd | 13 ++++--- 11 files changed, 74 insertions(+), 58 deletions(-) diff --git a/R/grid.R b/R/grid.R index cc39724..7a8c62a 100644 --- a/R/grid.R +++ b/R/grid.R @@ -44,31 +44,45 @@ draw_custom_grid <- function(object, index){ i <- which(names(object) %in% 'axis') definded.sides <- sapply(i, function(x) object[[x]][['arguments']][['side']]) + window = object[[index]][['window']] + view.info <- view_info(object) view.info <- view.info[index == view.info$index,] grid.args <- set_args("grid",object[[index]][['grid']], package = "graphics") + if(class(window$xlim) == "numeric"){ + x.at <- axTicks(view.info$x) + } else if (class(window$xlim) == "Date"){ + x.at <- axis.Date(view.info$x,window$xlim) + } else if (class(window$xlim) == "POSIXct"){ + x.at <- axis.POSIXct(view.info$x,window$xlim) + } + if(view.info$x.side.defined.by.user){ axes.index <- i[definded.sides == view.info$x] - x.at <- object[axes.index][['axis']][['arguments']][['at']] - if(length(x.at) == 0){ - x.at <- axTicks(view.info$x) + x <- object[axes.index][['axis']][['arguments']][['at']] + if(length(x.at) != 0){ + x.at <-x } - } else { - x.at <- axTicks(view.info$x) } + if(class(window$ylim) == "numeric"){ + y.at <- axTicks(view.info$y) + } else if (class(window$ylim) == "Date"){ + y.at <- axis.Date(view.info$y,window$ylim) + } else if (class(window$ylim) == "POSIXct"){ + y.at <- axis.POSIXct(view.info$y,window$ylim) + } + if(view.info$y.side.defined.by.user){ axes.index <- i[definded.sides == view.info$y] - y.at <- object[axes.index][['axis']][['arguments']][['at']] - if(length(y.at) == 0){ - y.at <- axTicks(view.info$y) + y <- object[axes.index][['axis']][['arguments']][['at']] + if(length(y.at) != 0){ + y.at <- y } - } else { - y.at <- axTicks(view.info$y) } - + grid.args <- grid.args[names(grid.args) != "equilogs"] abline(h=y.at, v=x.at, grid.args) } \ No newline at end of file diff --git a/R/print.R b/R/print.R index d512a84..9538657 100644 --- a/R/print.R +++ b/R/print.R @@ -68,7 +68,8 @@ print.gsplot <- function(x, ...){ # -- call functions -- - if(sum(view.info$x.side.defined.by.user[i], view.info$y.side.defined.by.user[i])== 0 | + if((sum(view.info$x.side.defined.by.user[i], view.info$y.side.defined.by.user[i])== 0 ) & + (class(window$xlim) == "numeric" & class(window$ylim) == "numeric") | !(any(names(plots) %in% 'grid'))){ to_gsplot(lapply(plots, function(x) x[!names(x) %in% 'legend.name'])) } else { diff --git a/README.Rmd b/README.Rmd index cda04fc..c5fe394 100644 --- a/README.Rmd +++ b/README.Rmd @@ -34,7 +34,7 @@ library(gsplot) demoPlot <- gsplot() %>% points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA), col="blue", pch=18, legend.name="Points", xlab="Index") %>% - lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data") %>% + lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab=expression(paste("Data [ft"^"3","/s]"))) %>% abline(b=1, a=0, legend.name="1:1") %>% axis(side=c(3,4), labels=FALSE) %>% legend(location="topleft",title="Awesome!") %>% @@ -47,11 +47,11 @@ demoPlot ``` ```{r echo=TRUE, warning=FALSE, message=FALSE} -library(gsplot) - gs <- gsplot() %>% - points(y=c(3,1,2,4,5), x=c(1:3,8,80), col="blue", pch=18, legend.name="Points") %>% - lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="logged y axis", xlab="logged x axis", log='xy') %>% + points(y=c(3,1,2,4,5), x=c(1:3,8,80), + col="blue", pch=18, legend.name="Points") %>% + lines(c(3,4,3), c(2,4,6), legend.name="Lines", + ylab="logged y axis", xlab="logged x axis", log='xy') %>% callouts(x=8, y=4, lwd=2, angle=45, labels="Not sure about this one") %>% title("logged axes") %>% axis(side=c(1,2,3,4), labels=FALSE, n.minor=4) %>% @@ -60,7 +60,6 @@ gs ``` ```{r echo=TRUE, warning=FALSE, message=FALSE} -library(gsplot) usrDef <- gsplot(mar=c(4,4,4,4), xaxs='r', yaxs='r') %>% points(x=1, y=2, side=c(3,2), legend.name="Points 1", cex=3, xlab='cat') %>% points(x=3, y=4, side=c(1,4), legend.name="Points 2", pch=5, col="red", ylab=expression(paste("Discharge in ",ft^3/s))) %>% diff --git a/README.md b/README.md index aaa95f0..bdf995b 100644 --- a/README.md +++ b/README.md @@ -29,7 +29,7 @@ library(gsplot) demoPlot <- gsplot() %>% points(y=c(3,1,2), x=1:3, xlim=c(0,NA),ylim=c(0,NA), col="blue", pch=18, legend.name="Points", xlab="Index") %>% - lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="Data") %>% + lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab=expression(paste("Data [ft"^"3","/s]"))) %>% abline(b=1, a=0, legend.name="1:1") %>% axis(side=c(3,4), labels=FALSE) %>% legend(location="topleft",title="Awesome!") %>% @@ -44,11 +44,11 @@ demoPlot ![](README_files/figure-markdown_github/unnamed-chunk-2-1.png) ``` r -library(gsplot) - gs <- gsplot() %>% - points(y=c(3,1,2,4,5), x=c(1:3,8,80), col="blue", pch=18, legend.name="Points") %>% - lines(c(3,4,3), c(2,4,6), legend.name="Lines", ylab="logged y axis", xlab="logged x axis", log='xy') %>% + points(y=c(3,1,2,4,5), x=c(1:3,8,80), + col="blue", pch=18, legend.name="Points") %>% + lines(c(3,4,3), c(2,4,6), legend.name="Lines", + ylab="logged y axis", xlab="logged x axis", log='xy') %>% callouts(x=8, y=4, lwd=2, angle=45, labels="Not sure about this one") %>% title("logged axes") %>% axis(side=c(1,2,3,4), labels=FALSE, n.minor=4) %>% @@ -59,7 +59,6 @@ gs ![](README_files/figure-markdown_github/unnamed-chunk-3-1.png) ``` r -library(gsplot) usrDef <- gsplot(mar=c(4,4,4,4), xaxs='r', yaxs='r') %>% points(x=1, y=2, side=c(3,2), legend.name="Points 1", cex=3, xlab='cat') %>% points(x=3, y=4, side=c(1,4), legend.name="Points 2", pch=5, col="red", ylab=expression(paste("Discharge in ",ft^3/s))) %>% diff --git a/README_files/figure-markdown_github/unnamed-chunk-2-1.png b/README_files/figure-markdown_github/unnamed-chunk-2-1.png index c02b9b8a785a1bb2fdede98818f9fae578bc4117..22954047dfccfb96da218845b3a6ccb1e3d20ad4 100644 GIT binary patch literal 8467 zcmds7cU05MvkxFax}fx;BB)4_9tbspG!YOf(ypM8fb?DjF@}!P5d{KKkS-u4GzA0{ zLydF@p-V3!2uREO2JiKE&-?$q^UljTeDlrD&g{%*XLfdWi89pJVx;4y1A#z{I@%gW zAP^-61frNcNd>grG`b1~zFG|RjIRUVAdmL;{I8fuK+j6b^#MgY+Um z@OTg$3y^^(C_T@*hQ;TfQ9#baq=u17_@> zv5IC)pJ~4p#@rz;AyJVUN&#=tl0qV9#b1Pmd6W;$d?k@g5-iFE2}ZRR)1WX zHs6A!)?n9=FP`)%Go0X2O5O;{|I-iCW&+iNHHBA}LA#@ezmA^Nucy9NRC#nG*&nTD z*>olU+2BTy!Z70%+DhtTSyEP^R5SE(&f7h{+eBVwc$uuBnD4ZS>N3p z2e(WRUfodQ^!BeI@3-+fLw8vamn*bh@3!(70K*$DOPf1Jvg^=BhZEn_zQybgGP2gZ#NPs5Y9o zu&akBn7r`)-X4Yn`8#xgmnutK08b;OD?75c`JYoRPGbsht+N3R5NK$Ai_9_FP;vLl zo7@;wq2>oOP6zr0*e*?-0Ocv>3|mtF7FwnCHXxokmR| zbK-%(bbAF=YTm>BgHqf?=x3h(TF~GvG+&JpaeHQ+KX-)<#beArV4G>3&Q~K(-0uk9 z%@sa4{S-@EP2-Fxnc7aC(g4+2S{)YtTB;1F{U8SCnFDuGm>Q;$yO-341#SlS$?g77 zDgKqtG0x9VkUn^}pGJ~3Tm7IMs#pT?t8zUW3S*o&QTB=Oa+fR7vrwb-v^@u$MqIy| zmgA`kR-btAV{M->Upf`wwY}v|S*3i-M9bUPS$QO)7G^JR_T-1a^inxhYA!vzNUjRE zZP2rSRrLt}!gGk|{sC*Vj30dbvvDe}MKyT1()CB=glsSo;b6wR`K!_FBkV zQP;!=CA0eMhXt-_3Be6CjBWKWp%y{pmn_gbKkt zl1oFyGC)IDLnM7Jn%p_)qHGZwLDKiR)a~!d-Tr!bd$rfPrqAup;E*!n`?~o1ARr_e zMk7*KLh6&x&W%uyAUk>)i`L;UD`}TEzJEYS%eo9|b;(qGnEU0<@9m7g^&*R=i>`R^ zK22fHjeIy_8lg@1D#!g&d&y@eW1UpPu2>NUo%1P}_{f@jD{3j;v;!+O&GBa}Xxk$r zi$49QOD!g6Qlh7%^?rA<~ZKCXh2`Ev`2;IQxjUp8NiF7)<*EA@*j z&A)lNTYKWqWU|h(v6!Lw@)N~hrSX|@CN>)z*}OoQ+5A?ojV(N_bZa^@iaP%$3Y1|0%SD(x1gx}NkHg|8^&9#;2`s4@Q z*FBjwSNfZ|je4tw+7Z6s)oss{Lqm|r(X}0e z@I%|19nXFFW!NB!-M%LYXr1>%e=|L9{c#!AegC;&Px9LL`rQkt%n6_8=EqZl%dz_? z(W4@u;)4U?QepEPf#U1Sm|SU-uJdXoyTh&aeJ=~=3^jllS*WRe()V-^tS7k3{&gRd}K9TN}z9vAm znMatCw1SY1JXMvY+U32Wy;mx}fs^+)-?6)0!bJHn}G-nmBc zcLO%j_C;F|9(TT(&JGx`&ozd{H)lcQBksaJs9?|jeDXr|^*BCZaPs5=k}vDCdz^fN zceiYxuZT?qee&2x#-;BtlR?b>B}o2hs&;PghdVqdu&e|TYNHj+CbacqN?xXR7)Y<# z3J%r&3I{91vjkPW1VG;)xL~;jL$hW^kKm{k&ZF8f&}zI{ zUz6k3ql8DLWC@U6JO~+SxIt2FVxn&6zcl zn(tnmQhxvOW*0dbJ|<_r#Ot_XMPbFx#ulbARb@G|hucF)!CbGBqyWEezpRu<7{qU4 zf*;sZC__w)t>?MVL3`-`IyYfQE!T(V%e;RPBk6-4P_NreWLxl4Kt6*(suZe4WPfKd zPhIhvB;N6s{jqDC$n^cgKH|<{pKiqQR_D4dj@nNu$X#;MbMlDxYykXSX z7dyxqq3Hti2jca7>~|fH#6%TEX_h4xr2NFW##?M1k^6b`vYcCaS#xj0?IXU~P=l=( zy1y}YtGGhlNm~nGwwCv>)H*N69rHKL8w6XX2mT4O;AeKaxan@`f~t{-Zg3!TAiZFX z^xJnMZTd7NcFQ~v2X5gtJ~r4nY~-a4%! zrXWg>Wk_4mPcVh&oys?1-V9VfxE9?mV~5}BzWsW?7+6XmdksfrCe2Pew`PN_T=7zS zb!|h}eCGJ`!7KT~)1XT~K`rMoFkJlbVH((1Jen%F4^a5L1uVC5kK4h~j+`!v*9xb31{ zI-_&or@83d7_hae*$K$yTi!oPLOV8vc+-+yRmy%P259LYvxl1qQz?R#B1)i!QbjCqTMowcNt#JQ{5M5 zk19=1fm_wFq2>rD6qc_gp#xRo{oZ})ty8E)vju6)bE#n`?+oJ*RJ9y2qQ&VfR1j6s zYsHF1HFHr>&mz#la`D0MzLeK-)zXHDyCc~8lxkHqeD_A0WUWM{bauY}^^;d-|1a;A zrZ;8uoirtr_Y!nU#xWg$!Y^z)YfcQaMXK#{#OPgF5VR_QogOpyNRQx10oQ|ptv->G z!psFPz%y9(#K@Mz7N`#_&rM<`_ZZR!1HeruZCg(^l}PanXXeGFJ^tL^)jCizNeu`{ zoA(T5Sb=&W)3^OJ2{lgFD;WddL*Z}TOZPU< z9PAFK z%VKWQ#9~2rzZ$5-YUU5{7>}XZMwG%3S}PCwkVP_=OK=#jG4oqp(j2UDBJL`oltbRBe90?nJ>#XU{lj`k8ul zNgqD=Ygl#!NN)G8ET^zvKmh#xPPebZBY@%)*p$5f?)Yt>3szBIk>;Ekm8#n$-T`D7 zj$6BxKk67Pn$ZKsn;DHpU|(x;J@$xL(d;DUz~yH;-<1uydJib73v*_Mlttciqu7^} zsLo|Q54BDsi$(fy%Agbr-tN0^%`TWviILnT1>}H9NlD6H7lf#O>YPZ8O`_qra1U6! zt)*Xv`sI(_Mu^T;b zfnwg^^`n%u7|#jz!^#XJR-SYG+U1K6@oU>}OG{ni5)O9nh8(T`oS8d&G~Iaj?v6p6 zmj`JF(a4`U1YVsWks3)_EPTRoG|~Mxq#Y>G(tf*W6rc7xb!JL& zN-!V%AwDS+t5ize_`vNu|5k=|qh=z+VV7cSZ7uF<4^hvLkSXKvw3_sTFc(PLOJQzQ z_Ad|l;Wl-#(~a47KQmiVDm72|?Ol(@V&4RFwdfQ<5Mog>nAeP$u-e?N6p z+_kg)eVBWz;3Y<`FNP0_+BT32A$|_$-*UIHWkTn%p$21e?Az=?)5r>5mx<)ewPYf3 zXQys|g@2S!$oFhx6*yQaLvy%tdpT>R@t`hvaJ%wu_Re=5xJ+fbZ$1x#;Xmr9KAH^N*P7M4+F~8YmGl^J+@&;qV$Z zJwJV-n;e8^k>8id?Jlw4>x`e$QRX<@t&dRG+sQeV*CF77x<~ifLqVY^i&wq{d)S!1 zs^p+-qw1P2J3QAAu)wjv5r~(-oDJVS(xKHY9W^k2Q0XM=Fz(G*-{@%iePFHhXfeQh zFdyQuV>0N^WT8r{PxMg_A_*#vt^tRX_I$G?opuzl=0SBYStB{)gaaG*ODg9N21<fOIT&|q|qKR>Zse63sN_~pu4w=wxe92vwOy{5EUGxE2rbGI!; zxkguqoB#QJ!%~#zU%%BF#Mnz?R{qe{YQ&68SO1L7^|41difRMcxLtJjg99#bWpQhx zTblV4GkMDyS{gd$*f#B(tfmBVeyQGgSjRAH@ihz4( z9`D`{Jf>Y=-?nkttucI2+Kb-iL_bJ(k zv*xS9!Z3z-ou#z&t)lBUk6KvFQqaIr#!|?I(sWxI*5PGXeOxy0I7$=1h0+P^Lb4RI zNIc#E@fZtOb4N7vJ%x$AohD*f7g;YWm+!>ux0JV(a7WUxa!Tf>DHiGEd6eY)q1vfg zUr6Mym5y>iyBM!4~DtOV`@WNK9fPdvw>-nw26MKS-2crWuIbgl_T8JAayx zaPPOzqfhnujXKh+8?9VEM)tzArmvz4P)+>yEyyY5jmkdu@SMNrpYO)=>%ODF8ROsc zJsGntavUoM8NF2i63@KXx{Ii%k)Qg6>iXiVR<+-e{V1$YXb1g=?T!?>74MoS#-MXd z{M1W(Q)#slC2vM*qV05wY2-*>t)d%kB+cB-`L*|e&%Thh zX7b~fde3*vC1F{ohtB)MHK&v6=1~2Q+D#0L<@)~_!BEM1?q4Ic=Wd$pKLaA~qxYIV z%{21f;ut#C8uffxiSZBt)URY5&S;x?|4UxK_nS+Zf6RIDyyT#@Pv4R=@fgz6y#>Xi zf6Q@rgsSGv>VYp&f29sxeZ^Ne5ceMf!}`^@pN;AJGv2_0DOv>phG)l3}4*^D)0pA|90>Aq}Deap6#YOEWh#dh;s6l<@Kii zd$wLXXpWP$Y0n2Y_b>4v;1hS3nCdY>#kPY8Y)iQU&-Q6 zmy`OcRK-b+8g+~r&5Fxy2$JpdFqd4|UW3qqWq-bX&&G#*#wKaWLweJ1dg}#hw5|k~ z2=mi4)lt0AQ3aP;09W0|qoZVvCJ)1wV=|nbSm?k%&p+Z8IYcyFBe6Vv4Ga{M(;g42 zets|_nc$M;>-o&;a_JrgBPwlA zyekq`Kh@dVR&L8&L~SUUKNAT68LLk5Klw0g8)3HWI_ULD0dCa>roe0f@+C}={L8>q zoKOFwG1bGRf)`9+WEq-IR_-Hk+0+od)jXpif}w&l;CWvOK6Yyt1P&mm_w2 z*kah$RhBG^g<+3VPW{1-`l$ESP@=x?*$~nvt%H*ovB{;A;9%En+Yr~CiGsThd9OZ} z@+j7al~9sJYJ!Q|U_M{ov5}Fpj%;K(k`pMo_l*a=pRsT!3P8Eo1X#Uta6Jblp%Z(tMFH_3&qV$I^YJMQ^w41? VdX^hyK>p_jo$LAAdwzH5Ku5cXrj^y#V9RENdOU0z#1YQDN+P9APA^HXcF2-kzPa~ zbg*#|5RB5KBS>%3JK2Eux85g zAbcbUPob;nA{7w+Kyy$cRU#=Wk^OWZeR>J0r+d;J@E|;%Zgg1T>4ieUQ)u=X^&$G8 zkox*a6;LD|6d8$+q(nyc(=zNOGwSOpcn~F0h0-5Mp;0KbehQ67x2~_Jo7eY8s`U5M z`e_vUqn}2j(K|=M)A}Q6G`iJ+peNW$l-_-27hMZC5Qz2T!RJVmbIx55h<5>_i8l30 znoouWWVHANPkRn_7S{D=+U3uS;P^K9E99mr>7hKWk7yCc@xh6R6GvZdeTCJ2mGMRN z>ek*8{0gD!8?!U$bD}^(3P|LWU?L~s|Ea28+E0p6t#TlXq*~`^pOR@F>;KVxJhegQ zd8Gj|2lkq9JbUSdc#aV==dZ%lvwR+4kH^HmG=TNj)vnyWtw4p}leYKLoHoi|++W^e zYtp+QLa_69vZJ=Mt!8cCo4<3-cBP}Wqz^M`u=AAo(!|cpdwIV=RX%oT?7CB)`dW?L z{Zw1WSaVq4{&&;AQ}^4^)O7>jV7euro4iU3=U}OnmGAfR88pnYI(GI}%$7%%M87t5 zIewe5OZ5JCj7oa=#aFtY&JA=Z*n^KwIMa zF^E7mr(Ch+de+sVCc_sGCln`os{0&wfNL5Aii`tM!MRT!?w-^_x{fYS6zy|NUh;GU~im4#-MHPXQuLc@pPr^H&Y|C}Tx@1*5Fk+I`r``a5epEAR z!Tx0cV4*A9Lw#iRi|wgRifj4V{kU2!Y6|YrHLUELbU+&3`E>S5@}N3FR@Y93(E?JQ z!YI$P%LVOwLafG-Nu863nv6}O;)Dl<4pp?t#w5XVm}OVWo*&k6YV4G9*y2TW9ThrR zz4yZa@rm9Zks{>f-%1I17)26*R+BA_J@e4GneiiSABaBQdLlL{rdMw4O_;0WG!$BIliQF4CSgI1)95ab zEPX5cma=%GZHD^o_d6?TyALm{=LW=&nQZ-4H(G7kWx1EHAlq*Mjp$hVE9^lc!de81 z$jOsgOEzlhT!6L^b4f+Sr702ZdROZ*;>V_! z=O>HxT52s__A-km6AKL|8n!Wesd!np;pxoZN@gIfX$)sGmLFX@vo6uKp;}9ui5Rx- z$i_FeL|bU=nKD~SJd!4q_Ku%~tX;GrDYdCS2Yd*oQw#TcnfDg6h4*&iO*ZzkNv7p< zALVoWH6Ux~0Md!z4@{P*tPqq9t(;$QFWsTAxB+2YKeLKP5h;mQ`&Enj5;{x%&s_L# zferF~6RuuceIO;>wx-wMV{X%()Hi&CRw>x{5bUTB&D>z~E72Q{?*CT7Cz??FWM(!c z&pz*OoxH?ch(mjzCuH8??-c+Yr5=MM20!(qhMJR@uBF4_2gBBlNWZ6pb}ayf-8K@o z@cJV>g8?UcL&NSsurc2dx5stR%~F}H;t-J)cDo62WJ367+-pEdKm$NJVGz(L;;8u% zc;ordi?T+CK%+?rFJ)sazvSceN-<`u&_7Lm3?~ICj^|~4qgyP4PmTFOXe%v4<>PR z>Kmk|C~`$TUt~Fm+>I1;9*(7kgm7G*Ri83JeSOBUN`2HQ+mIp}K{UK;MminL09COL zB;$6|WDk^?{XQ$ZEm){ZlsD#*+{!be$~rncJ=yk`8P!LaGro=^U{iw{Nqp%dNibru zqu2*;!A+ryu~XHMy6HgrlA7Y24m|k82{EQ7;vPv)r4dAhd52FLHnAaFNCJ3d&dzI^uFUf4`-RNtbMQ|+Xc-2 z5?(@}OVODU&by<6TRaL$e%64v!eTY%jfL{@M_{r9*}`gh+i>2SD1dx+%guNKUb z*C>jkPqx~2@!&cuk8W@0L(c6-f06#(#^h5oQ?PP4)SRcAzv#J35{C*^W@{A>Xa~kz z$p2CyJhhisTIBn&gaN7d3gHIzizS*3hc|Gp`gd70)%~QCRs>7pZQJF8Xbqp_#XrDc zvBE8#=>VV^7uu!@X`J3XqQy+UYusyc$mJk|3$K5RBVQiBh+_~-pnmxy1sjbHqo90( zNywkkm1gOZ$5;1eH=ghat!rNzF+-;R1%IByM+EI9DlbU zAsaa0MU?*SYflbmo|ar_7X+%8e#f3ZH;>$`e2he*Z@%HQDh0Mx3GdYjAYlYAG9wl` z<9bM_(5TFYNaSG{>4<4Zy3avG!Xne+Vt;sLj#+?(5jhbHWN)b68{Gn#C@pehBTDjzPQAX2GQSsVEX7kA%C9@XH~+Diea1t zlZQv_X>ZL*pJc+1CLuu>Qaz5OFp^M?s3?v&lPD&x36{?nI4NAnW7Lfi zHVHJ#=MU@#K!b&RNk}AS?qkTT0ngmT1Jl_DH(+`73)TyD`+cZWZCuaz9g|)u|J_t^ zO)7ucxUN&u9*a`Kog)#hSSeZ)Oyl^GQzw*g?4%g^T4+dXTsS$-Ap7i&ILf}?NrS9LghaAKY2 z2WB@$nGqZLcji3s9K-GC()CK#7>J|?X8;Zop(6E5OE->qe5bU!@*{Lm07VY zb@atQZ?Shjx3{(77CHXmIw9MD5vq6h1jQ|U77^ufD_2$L1^^)B%ur3HbeDsLdY|Hd6ENz4l0@aur7J_r8ttev8$bZ2uJ;0P|G&sknOf+ zfyHJb^0_c+`bJIRAoo#klSn0m!yV`km`on?vv9!;phQss=V@JFXJuYPRE0=rs zI4_m_9QTqKYVhx&Jz7*$Qo@)ux}zoq>|}`kwfteN71yBEkzK23Tho-rFK6bn*~qaO z8LOayPqY*JvC^UAjzZ=kz{*@wN9}CIR_{4K<1^kH=-M}chX1jAJm$9VbtbdZQ~Ib$ zo=x@kKx1m?F+_s>b9=XNsL3M=!dn)^(=v{h?n=8gG5{y9JJmsF2+zPW?z(=WK)XR@c zL*|bdP#ZnZIt;CedG)&d!biQ0_wk~2CDtQUJQ}RuyjqV`{o;L{{SDa4Av@kUuF@j2 zvqINnzSrsW*(rU^I}FU#wacqGKW<^g@F|~_y>QMlH5@tTGIn1>=~{^J+}I=Zz2&PB zwrP9E)Yc8~QJSr?t_m-<6vK12%LgWCux`NqB22hf!FT%=L@``$a`8o8$NDTJ{JyRq z7F5JzpBho&9i-{R-TdXZno%Db{v6QF*!+>yKmLZtpVTlq?u|W-&R`{3qF_~}vw|9S z_QdKhP8Da+^ODtuA7|yBq-ZbYc?~X_rM$I~`JrEGUc!U^I@zxlJ}~riqeJRsR+e*u zLFKg|;yQ;G)fWXz*cnp|82BCR?FZr7uy2C96Cyg|{7yFQNWE)??0I?TrDhpjKG`;0 z%!4OW)^NK?Ps`^vWxB_So`y~zhTb@AttYM-`M3JBUQHn<*to#3dFo(CKF=S;kIbKG z$od^C@Z?Tw5aR!JSy6&O8W~6v>SkOk*$z(K@Y*${ukTUFJF(e#pQRwXP|veD)u|Gm z!EwKFNpn(oxY3*CRUv|}INp&cTEp4d)qb09CfV+HV}}1y`4wLdxdFsyG$Xl&+g;<# zCNmx7`x9m#_=Xhn-DrrgetGFDGu2ycqxFy%$rm5XCw zw?+}2u2H>Xv;Qvf0`~!XP|H&TFQC=$+CP+gA)u}mMA1ZU)4Lz|qAnb`Mb9%=7c6%w z!6T^bZpB0=Pw?XV_7AVUGG7iGLI$VAu^OJ-tc_Uq`yLC6b= zy>k%#$m-XGY=6?93_J|+_VA;QcyiY@a^-$PPE~_r-;_>CrkF!0is;4uTzO`RJGQPi zs!Q8iaCdnkls<%?wv9=3%syXLz$`bj9cSwEN2|6n;*ysmh(%A>J+eKPJMNBb{n**P zjQ+{oSylt}xo!-PacAmTa_5rU{w@ZGSF-WBoBu)(jLze*w{AjMR0$6`%8FxcF!9lXj}0OlBYTXcJpZ}sWMF;sh+eQo(4yoc%niBts!7jOh!3Q zwfotea{|Di%xJbLaQi-sWzN$nhHk(|;P2Lo)P|VY(Vh67w6>%6)I_pbO6kaJPl!D= z*s`_tJhNDi_3yI*yB)2$eQA6N0?)nToi%dR;x)EbP3G^ej1I3cE$msy^dxnERKBlY zE>xuxPGHMpQyKFUV&`j2yhQV2R?;3M zO#`zTh-DVBZO>)@gq}Tf1SRalGHTP12;J z-tc;9FJp3+fHwB}5|)|}BVZ(Az6DeRS-uu6c(7Vm{`0GY?d{=i7SW>FS#0ER%2JPj z5!C0aCs=y6?d^KOsb#xkKcHj}h@(x6-#7Ysv#281n#mO<6(&vi9`bSL(pv#^_-bTs zN9uI658>$48TlM1>a1wJx6qT-oV~cJbR4znS3th@Z>{|v+Jl)Sc{{ND=so&H!q%lk z@->4;E5b@8^HRv1xhCZraUwc(xq`@Mga_lHcVrDYp?o<~6LRxPmInanmfO}HFEb!?@l1mhJ|f(u>>d4E)#4jT zIMg9nj**vPGYZ~$s!SFH@8l{_{df`W=QZAJ$lvHn!crUW{VZPi(*rAWZuRS){L(IT zvBFs%9hTCxT=1F+oJbQt6yzrO`2ZXG~gzT?YR+ z&D`MrnfM0_Tk)2C+G~{XBsz$w5~F2~vJxGS2_|aGFg*NqbY4;gc^ivG4M`gHcV4H2 zR_tY&)31y!J)b4S(bQ&IPmz`UM z=afaDDjZNBEAF(f;y7w3mdeTyA8sa$WQCV$Pn@kzxKe414LGU2RoSR(b(UPkqySl~ z_$d&7$M=Qu$b$hlpqIkSc*&{5h; zaJjd@cWK|iE;)X*>yHfJ+nkh-fm>Au{i>w@TuYO|>4l0uTQdFV=Xhd#?8bDis_Qlo zhnx#M)GB`)E;FGDB6Dhi%LXXO{1YM+X2;8eI}l|8>$n;hiyxY$njC^>aM<(cJ1Hi@ zt-X~%ncKXB1=cL((TJx(7%Sd;)MDk)0$j=&*e&32GA1*s4J7>Ofw=4);}C4O&LD^Z}s zwVTHSLUUkF!2`JC%zQb^|AG@HRQ@~MQvi+n7aSDKqWUj5Dr7vzZ}K8c55@cjD2pC} zN?h}1*yA11e2-xe&mnZY{1e3pv&7)iKe$wI?4s9b41H^yguoKDdCSNCw3Ud0*@kN+3@jhCrH^d5_| z>Bgxxw&O^#I^fq{E!FzgShs0eEhOw}{2iw4{emLOJI98c!ITbZR2 z2#4!X`ENhZ-10(Kmgo#7^P;f|OM5_PDqqm{<#5i+*d(;^5d7vUq4SmXO92tnfSe_bxBcYMZjJD>N_Jn>X$FzBK*pI{lhh1J>S%m$YIMIIv^T(6iR_W5eFb>UPz&}3X>k3b2SVzV*2@sY0&1E98&J*3!nT} ziLfTyhb|A}UY+yQ9@+8o357GS1fi-4K&kw3{65?@>nDNm?FICEe6Z-IO?%k`%_y?+6YdTQGWA{N& zx7%ha)RrC?ohS1d=s~=vv~pM_SN^TzL#ahr>ArdS%X@QbsyU{qsp16MYrD+tnDjbL zfyGoeDCc_66a_+cfv@xqRFQ{MzbrkZ!`y2|DeiLMz=+C8kq6x9W(!8=qX=J}?-558 z3_gcWe5?Ax*lb=SW)3fxF+Ne2=H`7qPw{#sgPEiSkBn81ye&Kkt8It^n=GPp-zh>j zc)EX;1?uAd_Mz2b6FM^^SAX&2@yDP--{9&N$sn9CC#Fmo6q5sflR>}3N`AB(k7F)T z$Ja^5Ax9)9$Lvs+rge4 zt0Ob%Q3F3}p2;i84lakY*7M#f{@f5CQD_WK;+vOa_RbS?psOw_6C*)x`+FK-dGwQ87g+CuD#V=yQS7>^)*0xx4t-W;+ z$;dC`3V(X=^3&R|-v8==dmivwtwT)fW?-%9tL5&T+UB(r>A!DyDyuhsD56?HRPi{` zyAWvHDLrv`fIypd=V{&Tn;zhgr_!V6jyjHWu}<5xWDtGKK~)5g`)d9075dqz+#09esO!y*Z)=Z~X+bVgS? zMTU9E>i&hdQ{(XwbfI9loc0OBU3?=ud1#xKwScD)@B@cYycb(y`b`1noLBnk#+QZ* z)cvjQW*L-UU1@xL9W2l`IJF01xK+&mZA@IH4ve_i!sMI2mL_J+-O{tzG?$CHlDpy; z{T^xDvB{33ltN?DM*Uq^7*c8gqTR8iKwF8NKP@x9D9(#&IcMT^6wX{NpR(eIG~=(o zJ!3}I{3u`zfi$NizCZZy)5hT29ag+4k5g{LeR<)`DBq9dI8ip@$Q2J0D8fuq$vp!Z zt@ed6e1Kv5+G~g-!;-(Bd+e6e4#lM=ht)z#0(YMgd-;Puw)Al!3&qo@n2| zkZR~Huls^$={tSMtumc1sSU-=t7vaDxnyLz#=YTXbXLBPTx8b%qlS)nH}qZbR@78k z6*Hv%QdJ0FeI}qcc~S9ubWm*976oHYdgXF^q{2Pf+1)8W|L3!7o82@UO!77ga}!HF zqMR030nz^bsmYQ$@davk91!j%2&>UUR9A5uePa!FQx1t@eH>J5^>GjGkE;3xl+V?l*b{M~x~MyLgDD-Z#0*3` z#0=#04NQ;28xk!RWOeL^L&_(++yQ;}J_-+TAdmSHw^8$JAj8O`l)O&evvDt9N;9Al*sSKSpX;gas}8Sx(L}c5R2c*~ z#JB@pS4B475|`hMDYtc}I#TEI3i#Ey2Oi)&6A20&d?KGmK{Za=vN@i@`Zw@0{VD*)=BdHhCCF+L#n>}C8nhwSNvoTB7AOGGQJM?beIU%)5KJU46 zziF()$3QigN9zr7=il79xi26XorNgqk3dWRY_a#XsdtLI>#_7xa1)>0j8Ko z*hEBB>Fq__Dl5+L>UH2jb-2PcF@`tyu_F~vTdSFdI1kT>IZ~C=?Wx{Ajpbf|xIOi` z{%z32Fn>jqyl$ez*Il%uKm;SoMne91NUch3v zE=@uyfqaEef9<)R1k`a zQci316^+cY@U7m@KO>N)G;zlVOuTvAzFOw**{tM8rQTNg`5Z;vRSazm7md83eyUmy zA`iclr73_CxUKx-6N)*!pI*kGQu_3 z5{Hs%Z0uLq*x?JS`gp|_E-86GnwHrRB)~y1*4c@)eJB6G`i(SE8(UiPVYkyif$gPT z5@T2tY^dS6;LLtzTmB2qQm^&Ho%PQG*1*l$P-+G^Q)6dtEAko|$65VwYKf-m$uVzP z)4&sx;#`g>?1Wtd-+X-8@QOUda8{HXxzfq~;>og7uYf18dX#ntI^v|Dfx7j32U#{* z|7D8^=5j#O;&`Yn$MKzuTIc=^Q_oNI+0A<$X#T|*!Ljqygq*Df%&$aSqF;OqKp^kp z^6q;FwNB5G^mm5ku`V1ey^gm|gldy3nF!e;R3cL27oD`@gZKh8!9pDkvg;3I9ZmIC z!w{=I@q6q7HrEW{;TscwNCP+#^)*2uTClWLHHB#N&E3^80ldC(x$xUwi&QJ&u%3en zTVup6{rcmHJ%S}`8&1RnCJ2DDf+c_sMjkvrLpsNZB0-q5jFzgO;xz@@C$4WDnr>tN zAV!ausoH+Yk-MAh$-SCTqHNx=06{z`4LxTi3NblnRLAdwgh~ECVG>|>S-%Wg7^}BB( z<&=)-rR#fpN0)vS6u`oh-o8KnSF*tW)@ykq)jmO*j@<(F#}R*j3nxv+LIx$yNxl5ZG}q-0B+nc z`O-L>CvR~x*kte_KSFPB5Y=+GylC%V!`AE0tt5qXk=~0Y7-;ExGZ_Dj)eAjpa?*yq zmM|M?WD5*Ojk3#r+_aZEuF`L|gsVtCe8*y+bv^AsaaTp^q4@pUCz%7x^2 z*%iU((dMrf$bKUt?+*`xLaoeUp*b#0T(d%D~m<`zeeu% z#S0DFz-HE(O14){Z))%D6C(U8ro)xZ!h*l7#hLH*&x3paL!_X_IAO}K{v+jt9HIEdHeELV|T5u^! z5lV?^gvQ-d{(P2i3$xrtncHy5|N4k-w6=}R4ep_LvF$MG(WU*{xv+w#3oQmpSuL62 zg{genFB^O@D5LxkeevC>7G2yo{z|F3Kge0C*l98LrmtFP7LX0{5H4BR^0fT#KfwPj zwv}}b{-3qBuP$Pu@MK1l)@KGM7x~sFIB{Tcys3YKE$O<#9;@u44J^9N!HG2eog>Xc zgUyRyWINDNLg72Fgcp}T%lS8(nwT%g3VEIE`|GI3nijlfU4&o3y#5We(`VzCqZJ}c zy>qZ>8*I7gXK#k$H(>N9@-1z9X$4P2JJ{+0JMG9G$aC4Cr2}7LBjP64U@nD)Sv#5e zG>P#?i9_ITK?=+*c^)V%8<>UE)6cc|KSv-VB;%K_El&$#yDT8u_?7IvLsLC79sh1+ zt+2_#Npwy838cPcJaBJ?ee<}V9A3(2(_$Ib3_N-a(atlqr{>r$bIC))@RvHFwZ8WH z(H>O>H)d{(Ra6}L19HinQ{eMYV2+J_0uB$uITBNCvQ>Mo)3016OPr*sGJf}4N8ot( z>emz1Uiv%>S3tFRw$h7M3VM3aFCi%j2;?q-nIW3QfSKx+F@ADhsS=z3f4)H!@5D8k znlyG?q@6&TrprGyG5M`X$Tv45i0v{17RG9u$I>W^9SUKGb&iO#6^!=?(NWZRGpaY7 zX>tjb?sum>A;)A3qZJ~(H0d5oYVQ_}=wzV`Yn}%3EE4tYyKkXKSj{cW6MFBQ$ML2=>m4h`o%Y- ze`h+!J9=>UMk>}8Yet8^z2nT@t(*O4;k5|Motx9)l7j2sM_D(mhwYR_y8&B^#*Q9Bdh;;B37wrtbVn>a$@0!!;lwnBHHrG_^C@X!AN>Xc#xa zqTmG1&gq&_;~!De8|t6B2E;8EKFJbWt?g#yMXe~3_MLtv&D}7MyUE*YsdhDJy$P_d z?aOiI_Bx4D+=R(4bS51od(x#+i=^S@ii38_Dd`+Mm?`Nio9D+Qp?Nal%+`LpvekLs rwcP|Cm>Ku!#FUV=n_oI_hd1LUEA2wI;3W68hUdJw&6(;`-uV9kLc{E; delta 4477 zcmX|Fc{r3^*eAn`hN3V_4Kw!9H}!ts_s6-HZg_h~m(|=cL{{G*xyU=Dznqe@ z*gdb+_WO6F96!7Oj{2xP6_)K5crQGf>xp8??a|Jj4K=Xck$49QwH^0Ao`nJZi?A&PZ zhoe*E;3TWOeOuLg%6es^Mi_qBYNVYa` zh99V87Wdin+F;=cRLubZ?fv#9a8h}x+*cYZ%d*L`S+Mq(VX#BC27>o|g)ujMWVhXN z+cJHWrFFWTy|3Uqd*icns*Q!?dDJ29f9)KyoktGxpS72PK@?5ro5m7t#NX25(WF#} zuldSJ<{==7BnXn_#%Bp7fFMIS1J&zHTD<;o*eNWd>BCb2(escYgLBqXaMa%KV(M~?@^v}C#5T1wn6aQ7Y6&Ss_;hT8nw8e1@xUuNU$Ddx+9Je#i{vZ@U^o* z32#cL*ipoL()W&lQZm!UrzbZhu;jKU5dL zIv(p`9WDCXCOK7I3X#q!di>E7^_I+?`nA`jz|9^d)b+O3reXt{Uc(hT-w`%*QP-G8 zoDWmDou_zysgHR7VhPDreBWB}oo8B(U#+aLH+KCu_hN~-SMZ8kDR}|$ciP9C+TWKx zanB!XYw*m$4N14}Yj2QbnN!iDZ8mbbw~tk(3Z1hN!P`3~kV57=YrPqs6*r5Ec}K;+ zzf0YiNU_SoIF=OjRqZd=QNKmIQ*_6#!a>yA`NHCq2Fmu_p=JOreC3+y@q#eVDj{Zd z1))X@C-8j@M?cxG!TMKu=~d%K;A}bJ^v-Ioub(0!WmOCM{{dW41gPcrLEtct)-5R)0o_pLu{jtn59sMu=His&Jvq)MEi-**c*4 zGpsRRMDu9jdBO{9ig2&mjrSzM{A)0(zo0v>lIeqVoJeY%^PZPIa=1rf&l}b)i@H%g zekVUbF0jsWSwins^-mfU+hi6ms%D|tZ;v#^22=$k-g-RRlsVB-MY=KWubQgF;92h5 ziLp5Ct(}LLck~s{AZ3q**Z2y$zbVy~*v@dOw0*pjSI_4q`tCg0saghALkk|qZrob0 zAHN=lOBZ^YNAb4LAO*ju#IBU?cn+6OludR%vR$9?0+R=sl2rkyw$AdEfVn5x0lv}S z{f?&W-H0Z?=&aoT_7;3G;ROb1S4K-a6^Bwxi!h#naCnhRl%B(tC*} zw-6P8d*_086hdFrYRMY*{Dlv#B7Sh_E7#oF{RN9IC=FJ<8k_jv}uv$=A>bK49kNk!zjdw zVek#Gk5`PObmHDnJk$roFtzd+|B#|;ViDnAx%3F$Oa-NI`rRt0-Pw5y$o^a+I<0l& z;ADBV9sildmoB7mE+E?R2t+%A)Nob+Bx!)W4dcTffET=lMoK(KAHGIw`XtyM2{}DK zVL%&>`q$qF&M?~-S8E`|l;<{bgySGsLd46nLLiEfmI;g>PnXHaiwAM;s(H6jg8^Hx z;YtniNCDMM1%U0x)8T0(C@+8(x<-q}lh{$u{L0}d{hTQWMaYoFsq-)>e*Msu4&F!- z1$4;olL~Uo6mk?Mz{Apn$WFfm{aX z;TO*y11-u&CB%aPGXL?(i51y`E&Pn)X)3fIO|dw^3A7}We)cDK_4{X)#`YKew#>)Y zLw>O=^Vv2#d7Fq`k54?Ci(nzueRcdV#C%;L`?FRsan9+>bK0K9853aimLl`;<%ebF zR;#PwBZ9aMM1(Unyy28f+8Zc4$})l^`30N+`VX@%oMqf5zo81(m%*qOar3<^EIsH} z#8VYh=nMJQnKfnU0Ifm=bGC=Iur-e|Uh4NS*<+j47%m-{<;IH5dAtc@Pvk?g_~u5r zdRDUg%~z^McXwSux?#O)tHX0{#+r6&2{`M#z(xwCuA|gB@`a8`o6U1Ek;@Z5#hKNJ zcj!{;P29dYYyYP4lLDV?PqrS}?ql7Vsa@V_7MtMvgR>TRF*cLBEQZl92&#MZtJmb6 z+eX;379*3T$IAidabp^__VpT8d9NIsjSr|T_>tS`fy$5HkNz+`x?8Z;iOt46#8iLz zwSLX2s#D)tXJ=)je@B1=@-g}5-ST5F$4$>5O{XF5pAVjnFB0>*vT+0YhVher=GBkO zlC_h`X5pKAdRJ*V5_;Uzp5Ml2#d|~3h~CeA<7_*{B9$mvb2Z!WrjlTVHSJH(j%0NvdcM7~5*Q~vTTl$B)H zcz|Rdwp`!sPsV({Zi3f`!jqz-$!->T%-K+wzDj+0hpc6mn!lG7sxA zjRc-!9RikWcqI`?eN5vZ%@kBK=0Pjo8P;Ad3p_iu?_txd0XyyF>{RFzC`hasFy$=q z{R(ACsn5T7sDd$1(%Kwg6ZlyAFLPIh}!KsJ0t~*|4(Aw-ros z{^jjV`-epD7{m;S`-$>8mSEm}G|G_ew|mG? z)@S#7peCfzWrc3)_^ii9()n=r$&j?4 zbMq-R&Mlc)9RKQM2#Fp-5z?%vBqjGkeGo0`3`5q%kq%lsuGs03g!fIp`~L~p86O~( z>D2-UE1kL$NrDUF@oJF$-SEH8*B+2)b*5DBN}w@&vyd$YHsvK87t!VqlIO>a6Hg$) z9M6znTuO(}F=*jPFTqmeFh>Kc5nQ;z{I^|&Y0*R@1Ihn=A;EC2_wjnb?ninX;zbO2 z?hSE**3P9X%aCq4Avd6*V}8r+GOea zs`asta95#9Q56jPBb|#Uh#`*2uG?zkejuv1%}p>65y3T=k+SujL#votEsoDlNc^5& z|Do5++Ecw09JFq-y1G=<(erJ^-cvch5fPT@#1Zn!`n#cNlcic9BJS4q=B`GQrSie9 z`XK!fXKLTyRDISsF~>X`za$ZuxH-A@J=7t^4C$-6bK3pP!7d-SA#!gIu6moXsZ^Cc z_Y2oynQshiw7NcXEJlL;8N-nVgBQI5_IYLPzek1A)=gg!|?zON@@-xDO(+vDfQl zL*lXzC#aisnVwz^W4h9oy1o3CWGxEAIjCRMJ71?`h?ZOa#CuKDk+ z_eiZh);0+@{$OG3*8FgL`xi(9sh>z9hJ11F^Pyc(a%YZtr^cRK+w>MUZgDHugcKa? zV*2}5KnOlO>I57Q6vxm#RwbKNKxPk27EH+S0Lz~$NHjq_od@5^ho?u1Vw}ysrOCIp zOE))Qj~6+$6{>s3q%~G$xaNeut#fdT-wDl}vfHHrv=EicL}dkC&wlT@ZVHh~a{3ad zAJCSJHCvi_-P%zXU6cNz(bKvV(KNVqcXPD|D#Vo9pF4u9yTs~kzW>js_koh>#diJb`lhearSFOfgMQa*o*twMfiyN&EV)Vhl^6e|o7n*Jr zh+}~`+!+ZIav8h5qzKGwrM)}L*~-Bw(ls%9=mR#9eR^k`nmPZO{N|&VCcU&M(B<>q zJ`g3An-VlE{vx^%HpbvT>T_`T?)8$2-)SXB&QZ94&#x$G)TACQNKY7~*FZ#^`$G{R1Ogg`sH#F#5&eZh{zQL& zA~6aIiaJLlq7a~{C`43MRMaG~3IRGtO-5A_tEz~^20hvaB5^VbI!PoFK_HSd@iT}7 zA{j_pB9TOMjv_%w_F@5pMpDD6ogO}O0fFe+&VLuW9MLa9AZ{~_`!EB~wDokFca!q& zfeH)H)7AxJH*i0T8ZjI4?lEMco&lV& zv_e7hB+-5FWob&V02U6vNc*o4l3W{><}e93ocGSmW4Jm=!r|6%xX@Z*VVy&hLrST~ z-pFyG*QxrNT`w7gfWnWej@VA)QdiH$?P1(7828mF`{uLtEQb_~B7{H(A%NyyVqm-5 z%s6&t+y!0Y$yL9hOKRpPk|yv(IGl1<9C;jX+Mq9tCOeW^p6d`A>e7b?!QpJd$;XkA z ziwRFhFN;-5F1QggmW_4@?)CRWr+1+p z&K6#Lq}N*g5|)@8S0X#5A98fkDL9785Koe0le8O9d{i6V3A|t<1c`fKRb56{4KjXB zl&bNxDxvgy@gKZ*$DbtK@L==ayBjy@_6-&!)76pui(H_cmO1XODvVm@zla3`Y-kik zzRp`Z)}oJy+U?%Y0LRxU&&9`Z+NTZ;&LU`v8**l~%m!o$oTbkpg%|q5jT|1MVs^ee z+nN}TN|vCax!yCn9*;QgHOa-HVmLIho4jVXiH&}X{8xI&Acg*uORw9>`C*tk&x1%y zasS#VMt{c2vI<)+H|Bm8-+l4RN&tBy@$leiHMQCSrO-Ax&5?Z}1~8uqp7xo1O1PS& zn44fAL-!E1F}dM082Hu;V z!+%wsd6xMgISUwJ93HybJz0PF4azNn_O@c^XSl+mB6gK~uV;2zc_x&JUGDLtMb5S; zol?xJn0M2^ft0|=H`F#jIvT`zspJIO!A`{A7nU|x?4yp6{BBBV}`<#=L zfpkR2v{|a%3*!RcKCE!XDdBH4X)|F5!p_^Sa1qGRew~xOv9j^G`^6hME#!-M0U=eG z_!)%Tjk-i1WN5#{{!eLpb=+8*P95*RYH-qPdi@Hw8+nQTke&M%Qv)2hMn|pGh|+dw zXml3J()bwfsir{4h=O9ASruYiRTDEsFY&#UkDzz*jBY1WBZ2YZ~Di3eAZX$H-6cQCqQ z+qxK;F(1oWIv5QERb83;=^ipb+?h48Eth3tfUm4^1mOgr%g~Fhr5Gd&^v{v*rco=2 z5YtnzXy~dz+@tTMC&OGFZlVc*ROsy-VfDoz1O0a1LPD?Tb&nlX-s4p;t@@&n!LU0w zha&xxz~5JqA0B@ZR?|B?4792D^=1}{k(E`b6+yy7oeX?yUW9rk+c+3m=GE?sDq5=t zW!fk4nYkaR<=xXN%XZ<7sN&VsV2}*Td=h|d2Wx*zsBm}PO0IiQfrJGlt^|9taC>J< zsCn0#dQa@77UZbH7LE1GVsm%Jq>ZA&+J0a3-v#7J4m;CP{q%#zcWs&mzY+pKx7c;X@9PgU9vwVahh^a`KFCbqy2AC{d!8iLYcL6Up zm#fTN%4`Egop-P31gj@HQ+zp_w_&D ztft7KLxkXhTV-;NI#gz+gKw#~Yh9%@28mE?DsY*@;W@-FG~>jm@B*GvyHx(91}Z-v%XkFU|L z_T>tob8(40`?B)SX!^D6?+OGGIPPvh!LmaC4i-N(#l$AV*}oEhc>T3XG>2Ykn;!d{ zars(3cP~Wdy8Ipmb06Gq0LfXJUR{K8udNkF)wVVRzBF63DOnj@uLIWWzLN>*+Gz(7 z2+cD_#g{NINQK{gxYJioz12DN@674+)_fI>-qIjPm>jNzomPq>UQ*#3{qfQm$iB2c z>CUNE3!Fy%4X2VLzqWUpDYj{iOPsZ~3}5aUDw`Rmb4IhKVmqXk z9b`MJJtS4+684`duVvsR;P=TyANFCJ>ePKpIA{OLcl)xM8$yqFPJe5Nc3_yF{X`Ms zX8D3=41xuyQ;e@eApoGPe~opdt(sq!ky{`Mu=H|Gnv9sKPB*Lnn|)I3g1o0MeMU(()2moJKU-D;7kQk*nTc4$X|wW}Cz|F}`!u;}T)jr-gGZb>?R zvQ2YX24_)^-$_`gb%UR-99!PhgdE(``y_iq^0k7Q8Cvc==lWEv#dX^$)ZlA{3=_2Z z^hPmve+2odw=0iSV>Ei@imQ9y_Eg~F;`-oGOYuWptU7(5;COI`=sHe@r_%_RSj~lT z+wL>bt_*k`8ITl!5O>X6*MYI%Fb^*(+V>Ac>evQ>#q7VWX+lyK6ag8pDqseRH+A{ZbMELp2)?69gZs7`w655LiM-R@G_ z)~2zQKu`DZrH~r%^}=3Nzbk+EgUT;*0^A4f{3|jP>As?sJ1-g5Ejn|T^YcF*T@$(D zRSQ?C?Z*u+a60D82`VT&yDyX^VgoT=JMro6j?Fz`CB&}HwSi`W3sJq(@8rgCdsgs9 z(#T@(BYdPlee@8AtWU47fY#7-Qn<3(tJ1pPdd7R9Z$=EBZ|7hxwB$l($g6g!dD{gmKfEu6K9vgFC&f^KiKMUE0yo`Uhorw}Z4E z`J~?~?(RlamxFu>{x;|q{*^rC;M0c*k^^dr_y`o?qC%>iF{RH@U;aLkwIw^H_v<$1Md_ z?^gH9y97TMWdbs3uCZLn_n|Yy|{a^|tUMTZ)WKiUS853gz?hYs*_~ zLMQx9u@#K1RGd77D)hD@0bB185ZhK$(YN`JpB1-6eE{iTd^82Azkf8=3U^<8&wwOro&?Gjr1Rq z)kTH1`SEvAW@}dCtgdT8=>R_ULj2Q9tdEsv&W>Lj;zPC}p2lmwE)ivuF+-uJnT&g(FH!n1~kyDR83{>E9} zjO!1LpN*o}Q{zUdSybM8=KPMZ{vPTrnk5PvE`3ZOeh}p>BrcdI3d`g z=EwXV#wwua?@zqq&<&n^v~=t^IK0}3{*TH03v%waqei;ekobHTn7T3ia7kyx+a5NO z)#wp0E@78*ov{m5Yxx8v{np?u6Q@z>#{nwJq2UDJ|9FM zQcRJ36%~;Yn0pOfjZ3+(9EmC+c2EzjUF%o+hsjkszq3$1owd~a61{4;FtT;zdPoVdI!HPC%EVCRv`X~H z%Rx3uarBTFZ=1{5JatN4#^vzokabM+`0+Hn$YMkzJ$2KLf!J7c9lAP}Y-^U3@W&P(mW>PVjkOj@y( zt{IIsfHYxjYy?s$KMHi`EvZt}{yb}=t}8997DEkCHC}c&gXPbO@h+)@0@-AOhVsd^ z;6oiAHp(|p1K(=ZA47|Oac{>T%^BG-&R#C|| z3mXOkKM$z|mkTZagyjiPrHrnj15gxK;Xm04?2{siEv!6>3ePCHdlH;_ZZ-!6lz;0P z#x#(-vFp6ZiB@k|@-`WnD0k}_(S;O#^ap~XxhtL{%7r*#iLwdutMl~-cWe*u>)&zB z?Ae?H?8T*DE3f|Jtj1!{v@~>PZcmfkcW$9|PHQ~)#kV{^*zjlObXe-F=#~NO_~6b& zxCd#vxOnjOP`LADvGo&F-6fAeQS?+RfA!e6Je{QjC-^?2f?Vcp@Tipm)z?dKkbVDXG9_ zfJjFg57wUW(Di0yfmHsSLurl<=2>8qZt!ahTIZ~~F^B&o=ey=lwdLdx09q=vB#6A` zi@1*Na~j-+yNmcDuA#>c>5{39FX0mWh^K9jD$0*z8@d>3TElAF{D8D24C$ zNfez}zr}?c=lx*VYpc9E*SI?JrjI{(g+F%m&PB=oh@(H}5j+vrz!bPnIsdh}O%*Oc zYFrMI20DG}#OjFo8piwEI15nSH9tfuG{245(9{@Mif(CKrLWd13L97YwSPiySdn)6 zBF9KM@KEWKa_>d8BZUSJ(~KYOf*N%}H#1KQ-l|}%I2w1dGISlc^bjHr?zo|8MFBDo z<36oAT67<)>q>m&ABC6}pSNlAVSgjtlRibA$Cr+~*I1G{XLeYFR0;3Rh}!Dgb$q4c zu^Hz&RsVs%es z>`k=PFogHHi(KQOB#I|}AZf4gMczKm1-`@Kux!-tnYQs(oulNhfJ9&G2h>;r#P~j0 zFP&LbF(47fS3^4E(2hZ|4!6ZZO<|@9_urGY|5KR3ujtJ$hd>DBS5aChRQUz*5E&9L zoqr&T5jo5hr{t~2FM{r~q>}BS?xm=_@$!|J2t3pABRSdzxorKc^4piZyYU6Tivwy= zsF=EuyV?@g@!)OJ_U=NNf|1hIX9UST{bgs~J z@-)fU9W_1lxBWKu>uyFVarap3=Fu~*^41^`c>J$z*_N@bbv)+Qc{Gs@+^#=-9oj8q z2KjBw4QWs%;{N;(OcuJB(bDGLiFc-@e?ay}CzZegs#w{ue(GMHrn~RKjq+(pzN}PV z0kiqo_J@z)k9q!c^E@^VC`)@q+AUXOa+SR@9Bx(n;(y&Zw}4R>OgS{q4h#H~Q(@u% zUUXIf`BrZ(?wqO`8alQmnm85_@@M$sCY^{oE?d&gjZBf@W{2YKr9gnyo7U}9RjZz{ zgK*9lliojkxKs}e$zjcBBHyj|M3=Xora5{0{LvJDP2E@R;n>j}u|>Q&QFQ|a9AB>f zkq`8i$!CS&;yM^yk9SHL$nk-H(HUL9HhE*D{*G*Cb68$!xD-Vr(dB)aZwYE6r$1(2 zPtbZsr6F8O<7i(e?(OCwnYHM$aw}KC;&ISco_#8xRV5(aWGAl+Td2$|U!L{xR!oi% zM5o0ZUDt$FZ=dX%y-2jL_gTy8i~nn8*Q==mh^q`G_hB zLV11okAEv8LnER9xsrjQ+jZaa72loRro$f7wN*_XNL}bam~MDVctlWV$I|5Lh;GL8 z%;>sqkErl6hcV6Sz-U`!WcJ=2SF_MeE)KmOFOoX(J zQSmJIY&+TtP6@}}?ym&aHy!1h&1t}<0lUr~QWSVMOIdB({=U8oq#8{X{drS6s>6ki z9vZ2_#--}$j^_Q0HH$)hO9D|x@9ne(0l>kg3&2#%m6cxS6h>R!#|(}Nc>HUQF;7$k Y6-VB_W1#tResHXzrgOjKo(1aP01ox%QUCw| literal 8330 zcmcI~XH-*Nw{8>+g7jXbi8MhlbV3b9K)Q4hkf5Q1AiYaor56FILLwj?5s}_R5jAXAd=QGQidzHP{lPCi{4GJ<=G7tzvp{1$z7zDbG z27#{qxk&^_bRUa?flIrAjUH3I#zEL5Lba2Z$&@ z0u)ytLka-_3d1GjS z0-)EImx)kN;uRE;hyW!fA`)v76LFU{2+$P-msoRIQ*(LQWJuA}blG%yiA#jyaF@8t z%S#Xlu)q8S0-%5zP+VRD&aSWk3efj4DW(9OAbqK6@d^Z@Y`^+m>u@i64gztyYN^4D z{XT4F-?GEW_`KwH(tZg&C>D{NHEWE)n?Ewp50iU++hE4!;-b5-L`1Oyi@pFrvS|4U4}&8=NRjmS zY-LLMi_>C-qSD-oOUp+Fs4I)rM+3|5_1M50Q>2T^W+Vzt7iIVzxIqG-6E?Vil!l9` z*~XmBRQ_-R>^W|q!Tz>d2TzW=O=~F?@&B(?T#TUy3F&b;Hr_S zhw>L|RZ>x#^DR@qQNC4ceaL>xs#{V~3@~G=gBwsUrZofp%b@BgRSl2P=LhYkl))_l z(^g*$X>r)#`f@vb?LAU3s`l~a-C?oS?()-!rbg!TFPtGc20HWBA3|>GS~=vzifO{z z>o!m2vV!{a>fU=g!@=yqW`wRMb1c~DAv8&o(o5zS%tyyveCkJc@fW?V{D^^{$sGwV z{Rm2CY@=}xJ!+e=X8g$bq;V0q?s#rDLKIyovgR^2;WGVb9WlUY{}FIhS2<+!MT<5I z>l!*)_TDSHbX`J=ZGRNO+cnNs^1wf+_T~kBwFec+?iEj7KJ>^~N8@}(sI>9AOuf1| z^yZ__RyK>ajT$fW>KgBJ5+s?*;u>e0j+C(qGfvXwL;Km{zgUc^&q4peqzE&Ez>0R( zi@(FI5AG+{1$lT^_*48b>M3oxL7OJ}882CJEhyT5v{re37dzU#EE%Q`sW@fSeA-gi zFxCX#7F;%&y&l!gWOkG}22#W}ty^+=oXoFV@3C@GLby!~-liwsi&WhJAFrK}fI|1V z_?{EzQa7IM98KmanT!rE;YQ&qdR*YjElwv(#q;e-r}73pVNeLFmQ)Im7IvTZU2I3p zmf-sz_FU$fYvgL>s|~Qr+Z4;jIQ8Y9ExHTmeB{T|O7zs-Xe0L`iGz)n?JdmTEXBC2 z{YA%_m_?uPjgPaofxJk%&>GHos})|momg488@9HFK4v!zugtPvCy=&BCTcE^)ONYS zZxpS;qU`(KGW;#0Wm{+B{9rlEcRT1)%TY{;vq(AZ-fJ_6Z-HCN`fAOymrnz~S*%X_ zlim@|Y2#gv{~0wuNC9Jk<5yh;7^lfnxR-mHNU?cYpkC*`Tc_)o4?Fjk$sLt<95k;7 z)$T;sf8D3h@|KVgQ0-wLT8UCehKpgILiV!#ByO)#%8Eh zhlZ^kz~5Y@Tr^yft#PA^IVG8XP0lFW(dIO7*pHS=q}{(Qjf&C;4#z8lV?NmbaS|(z zKP5uiu?UO(diJIblb55+0@oug^GY)xApyb)zCQR(oA4R@B2t$357umc&>Kw-Njq-Q z;T;{6{I|(L!OQ3k=<6{@^7MxC>%?8uuWoM5YR?;z05?|km|8Juy+{&pr5GSU7p1-l z_&*#Zf@;b;UF)K*O5pgdIB#eKAicN$%)DDKVgZoQW5yPm1lBMyjEkN73)ae2T0kgu z_%@y_M^{4)c3TB~wQE^x2Dk+Kr7qP=;m35PO_A9=@M$#vW6{`7_IJ~S`C zSD*KMM;AXm2rtP4sw07bnl;hK%)3vO&?#Pq%I%C~BvS+Y;6M5GZEt=qOx#^k) z>diC^-=i|bpf(cu36B#oL^ow^dkA1;X=tI z)w(XwfSj*g=vyj5AOI;g4L$L6s7XE=k3Qb4+pEiApYWqcF607;Ie2_$J~UbkL;iy| zgxh=ZnPCcd&F%Y}-7?y{SMjWzFy_v3BL-hUb4Zdx6fn2%3tGbrU(70DT!(DN++jm8ShF&_!)|^Zk$a zyE^x-;I}^Jw(7t%e*o~t7b%SzMldstB+=BotY)J99oM^wGmT2zJE%QYtjxecszEuO@2J$aETI`4CQ z<#`<>%v3te7-JqT8LDv~dYwefX5QJK8+qi(Sj7|H{oq!DDo;s#fbO$5vdws|?u>$_zA*YwJC(kprXoPLW+N;A~ywh4=uSyu9-ZJT)yaRs~z zHuONCRMkIbP;q<h+I0rBvD`r^2%VTlgws#akdx<18#jNLX4srg@6?LT3ogrnYn4 z(zzv~BQN+H?HGw}A;{#5T*@ctWW+s>H%s~FEJ#%r`Nc-zyA~Jr>uC z2sm8Tv^!cK_9qR%ou8kNl|32|CL4&{u^+7b!LilPs+G_hQnGbf?d^&+oj2Lgk!K72 zX%T5UBMMtvcee^D38>p?UVp&_ug<#E*8Ne92lbr#}6HzPm=8z2R-y8KtfGPMz zR$m?#O|a!u%*4QW`0*+u^-w3j!;8D95FWu+xggaIN^hZuas5_?;W-?8Hb%i91e~LD z7$qn((w6s=zu>+UZQm%`qjouPL*B_J)p6AU`|wBoY1N}V>gv*X)(>zRnJ1O+Uj78@ zVm>l*Se+80(r_km`3-kYm%IDmS~nlLP@K%n(Y5#F?z=~9q~fIi8J`<1Y<|)-IQ8+L z@q1s7?C-sCc(G_WZ)T^{Bq@66dDddFt2G<#F171)Xt?UDMT=}merUPYnWV8|tz?H7 zHBf~dxV2y-_fl%j)v5^3Q=*bonM(2|nY;(I$3&vMc~|usU*?Fd4raDV@7`-e zMKR>^C#;9O5cW)GiLmGU{Tp@^K=ES0T}c{D(aZp+xlwfIeuPh&;X;McFjl2Lz-TMD(8&QT?w>%TpUEx3y;FpYGA-Gx_cgdUqqF9wFbg*ZTb zkKbaPa-V#8pYFtwT^{%M-m;G2MVY67nyptVD^@CcAG0YG{lIXtL!UG%u@!$Cr2JIHJ?z_yda|f8XQ%HdA=Q*76yw z9D7@E6eT#jWcb#+)Vu^{vJZD-%2pG>`AZE;r;2^N73*LSz?V?O6;Rxhq(8t%dQrq4fTutf3N5A>zK?&^P@ z`RIXy#{<5Qnu-wXp8Tv?NpYUa#q$Ztr0_NVc>^7rbX@ayho_C+CHu(AZivA2hHma@#o*~ z_B743W;v?`XM*q75EO|ERS7;*@$kPp0;!AaA#Ay#YLIhSExT{Wvj@p?G1$8|Wg0zfoVo-dTCy_snd+;2n$#tK{VVN|=s+8W4x=k9HdClux8mdAom^-=jDF=Nk1$Wkk+?b zQh!waS2~)r6Ayl2Ijwi@s2W81W+!7E-xRpz7bCq;XO_fSnHSA0;rc9O9j{WoSo|pe z&3L2_TW0F;L+f~Wata2Os%9Dqr>iW$`=_^JIcrg*M&SX2f{}HTkH%HX*0LTu$MpC- zRy>2AO(~tOcDhs*wcGI59v+w248m`a32WgnIt7RNRU>gHv(9`3- zpb0Q!bs6K(Z%)#7MuTJ?36~+TWED0=#|3nbb=SAE;8HXRjt9aa9z$>6jEj|Gxxl?3 zptBDg+n@G?jlvf+VvXtpld3EEGmhWy>6c;cmje$G137tm)Q-eV(dK z1Z;(^Me!v|#bR~Lg}{&^76@+G>HF?(KE*2t(eG$oFim!M@8rN)uIEbS0{8lS)z?#e zD!;3FYW^!*vK;(v^E_R1LV zd5$T6@E<_46mAC{KuM7gsTzhuiEZQuERT& z_p$bpk`ChI4v48FsI5|~;k;&#Gs11lN2&;q&4VR~6QQBV(c1l>15vZ@)g@<5CqpA) zdbn(kd1(i-i`#7b4!VT&y6grp6DIw5oZN}4P@Kosz$CmRL#RZ&PSSz!!#eJtdPQAl zS=wfpojW@_%oj}_aQllyqfOK4#qcVL0_tY|`{8s$%aR<9$KRS=BYvm!S`}UlWo{vM zn=x(!5*v<&;U%-hgPxB2$Q*s+;qL4SL!0{wHS@E+NXmo)c|8Uhj)d0qPKwNEr3mmQ z^f7|ZcSFQjNa~$Nb^%yHd@&Yw7W%au7HE`1KB;$4espF*%0cYncCc@?M%JU$7NM4t z`wDkCFk597JOvr+ay-8J7vm7gq5@*qemTiK01V~QhV&Zm%hm_Z7v?0x_`L_BU?l8Z zG;9*t^HtHEMv7Q3XWpJ))BP6@o_#?s)G^Gm><8mC0yNRYy7>n)*Ls~9WBf#7WUEwk zYEwJPrU*SdiF1s3c_9OT?f%lZx7_|o6>cZ#06qL>@gDn=!3 zV9RF9>4biyU)O+f)Cj@14WLrB|Y1*h-+!IvN{Pp-(w;?duN3sY1V%>^q~c=`)iu& zg8UjopwLiha1C1N@%_=7Jd3@esx2jtskaCdM2-75DTjsLu&k=&%35y2z<3Vt5{8x# z6GeGWDlxw>dV)hi#%I#U_?8o!2c6@ViB3Bf*%am>C#{dn!YMiWHI&Ss7yOM)wcIY; zOi5U-KQ9(j>!8$cIJ_O=+q@@%R7Y^k^~U&rH+1>zo|e+sTG3g*oob|L?KUbin2h>0 zew|b=;;bgee_*2{I~7*Ggm1j;x0PL5sAF`x)HSTU!OEQdz802t26HV8lK8NpgQ3*# zIy$WLL+$9<=f2?v%XK>p=_WF%s`KT^Ap(Yuxrv!k_4#Fvpkj z!b$kN10T*6=aBq~Ncf9cj%YRTjA1_zF;WD(hTQYfOcGTrbs!HQY9bs`wVLUt5v0iU z;Ct;=0`+GX2`n3hL9xrc29-ofuNCYdtGx-W(sKSLquG-leO5ia=otN^G62Cznp}B< z7Q^*BC2Kas5F9My%I6HRuGarPhz3FdojzRn42AkIe-*fjRdSd_xM&@nq)mCSAAXyF z9`@|&@FM;GX8c;`$HR$m0Svyuv#PqJl-Xn++L`_3!)~Sft05Yzd7_r@!68_z6AAL;`%k!v{85e6Ak?j42+R@uBC%pV(|@r)I3n9}$~d1aB_;OAu{YhZYnWlr1T4N!kQ^GuHbz(Onw4h`dw!z3?Y7Dn3wqMf1eVj$H3f{w?M3byd1=fex9C3f zf?lBKQkY4lpeJzipOQO0@c;D?Po53KeF|SsN}dEfyM$jqmp#X4me4ngA?wEjTrlK( zV-ua(gS|1FEZ^2hOl%k{TO%UItDet5q2U)rC_%Z}(GPLyBrX^gHZNWnoXNJo&3CM? z&~?DQ!5=oTb-?H8lx3@J?`b!bkDT>C*=4<_gtH$p6UMx{^g8a!>jU-*$h-T`~h z(s?_Joc93dCdmT3DKLSa_Baq|Uddh_$6M+AJKNpj)W>#>$QyJw#GY)iYufYxr)+lh zAip@P6opriB7Ir*Wg|ttt70e=l+9NSh59Ol<`aPqZ^WsGq$magIR>~C1UYbEEHF8c zxv>+Q7nBV|o^o!M5YF@{2&=Kul3j(rfeVf0){lz4)-HB0l0~1X8o1&ETJbFbae3W@ zlaz#JgphUVc$Jj!Fsi-n4#sEdH=N^2-zlk}AG4E^uy(<5SlJ(Z?2Ttq4;$vLWUp;b z=k=`~&Lq&`_0H~Q5KncXUAq4cVAN42>M1V(Mc8cn|s^=mp_(t z0N(4S{xE1hE+Y>md(Uhfc{^Xgw3FSsXh^cCUsDCcr4E5O$a29T_3cc=wDfeLjKsi0 zOn6&lsGOUivi9|9nB4$k4m)mU&KR0X+(7hVAWxFVhSQk*3GFIn3Jhlza>vHj0>7>P z8qbwMYkY1&ze+jT94}e|SfpP6Cj3C=v%=~6aP;PUtyodNfXX75BoNSo3vv|@EKz}N zVy``}VxAhKPfsHk;k)7B$aNpGV}JDvad7xcTzQx~SWhi_PB7*;TtP(MkpKhj6C<>`W zE0HsLkH@pL;WvU!~aL$CSHp$L)95|GQH$a zyapc#1K3S+Y9yF=iu7(Dhu;Bb7n%gLH7eA&Ae6ARZuYr;Pn!ckN;Qt5oSlFB$d6bD zwKT{y?;hhDoU9qHGEOS+u&oX}SX(lEpA(TMIw}+~S@a_Sph$`CSTfpN`#29zO#I(oB)qe`K)b-Rpt2_(;KS-1EEC2ui diff --git a/inst/doc/gsplotIntro.R b/inst/doc/gsplotIntro.R index b4ab1f1..f8399b5 100644 --- a/inst/doc/gsplotIntro.R +++ b/inst/doc/gsplotIntro.R @@ -18,8 +18,6 @@ demoPlot ## ----echo=TRUE, message=FALSE-------------------------------------------- -library(gsplot) -MaumeeDV <- MaumeeDV sites <- unique(MaumeeDV$site_no) dates <- sapply(sites, function(x) MaumeeDV$Date[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE) @@ -30,7 +28,7 @@ Wtemp <- sapply(sites, function(x) MaumeeDV$Wtemp[which(MaumeeDV$site_no==x)], U ## ----echo=TRUE, fig.cap="Fig. 1 Simple flow timeseries using `gsplot`.", fig.width=6, fig.height=6---- site <- '04193500' -demoPlot <- gsplot() %>% +demoPlot <- gsplot(mgp=c(2.75, 0.3, 0.0)) %>% lines(dates[[site]], flow[[site]], col="royalblue") %>% title(main=paste("Site", site), ylab="Flow, ft3/s") %>% grid() @@ -39,9 +37,12 @@ demoPlot ## ----echo=TRUE, fig.cap="Fig. 2 Simple flow timeseries with a logged y-axis using `gsplot`.", fig.width=6, fig.height=6---- site <- '04193500' -demoPlot <- gsplot() %>% - lines(dates[[site]], flow[[site]], col="royalblue", log='y') %>% - title(main=paste("Site", site), ylab="Flow, ft3/s") %>% +options(scipen=5) +demoPlot <- gsplot(mgp=c(3, 0.3, 0.0)) %>% + lines(dates[[site]], flow[[site]], + col="royalblue", log='y', + ylab= expression(paste("Discharge in ",ft^3/s))) %>% + title(main=paste("Site", site)) %>% grid(equilogs=FALSE) demoPlot diff --git a/inst/doc/gsplotIntro.Rmd b/inst/doc/gsplotIntro.Rmd index 3a99545..0a550a7 100644 --- a/inst/doc/gsplotIntro.Rmd +++ b/inst/doc/gsplotIntro.Rmd @@ -42,8 +42,6 @@ demoPlot Data from Maumee River will be used to showcase the workflow and features that `gsplot` offers. First, the data is manipulated to extract the timeseries as four separate variables - dates (formatted as yyyy-mm-dd), flow (discharge in cubic feet per second), pH, and Wtemp (water temperature in degrees Celcius). Additionally, the USGS site IDs for the sampling stations are identified. ```{r echo=TRUE, message=FALSE} -library(gsplot) -MaumeeDV <- MaumeeDV sites <- unique(MaumeeDV$site_no) dates <- sapply(sites, function(x) MaumeeDV$Date[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE) @@ -60,7 +58,7 @@ First, `gsplot` is used to create a simple timeseries graph for discharge, and a ```{r echo=TRUE, fig.cap="Fig. 1 Simple flow timeseries using `gsplot`.", fig.width=6, fig.height=6} site <- '04193500' -demoPlot <- gsplot() %>% +demoPlot <- gsplot(mgp=c(2.75, 0.3, 0.0)) %>% lines(dates[[site]], flow[[site]], col="royalblue") %>% title(main=paste("Site", site), ylab="Flow, ft3/s") %>% grid() @@ -75,9 +73,12 @@ This data may be better represented using a log scale due to the range of flow v ```{r echo=TRUE, fig.cap="Fig. 2 Simple flow timeseries with a logged y-axis using `gsplot`.", fig.width=6, fig.height=6} site <- '04193500' -demoPlot <- gsplot() %>% - lines(dates[[site]], flow[[site]], col="royalblue", log='y') %>% - title(main=paste("Site", site), ylab="Flow, ft3/s") %>% +options(scipen=5) +demoPlot <- gsplot(mgp=c(3, 0.3, 0.0)) %>% + lines(dates[[site]], flow[[site]], + col="royalblue", log='y', + ylab= expression(paste("Discharge in ",ft^3/s))) %>% + title(main=paste("Site", site)) %>% grid(equilogs=FALSE) demoPlot diff --git a/inst/doc/gsplotIntro.html b/inst/doc/gsplotIntro.html index e37076e..9ab3dcb 100644 --- a/inst/doc/gsplotIntro.html +++ b/inst/doc/gsplotIntro.html @@ -53,7 +53,7 @@
@@ -85,7 +85,7 @@

09 October, 2015

title("Graphing Fun") demoPlot
-Demo workflow +Demo workflow

Demo workflow

@@ -95,10 +95,7 @@

0.1 Overview

0.2 Data manipulation

Data from Maumee River will be used to showcase the workflow and features that gsplot offers. First, the data is manipulated to extract the timeseries as four separate variables - dates (formatted as yyyy-mm-dd), flow (discharge in cubic feet per second), pH, and Wtemp (water temperature in degrees Celcius). Additionally, the USGS site IDs for the sampling stations are identified.

-
library(gsplot)
-MaumeeDV <- MaumeeDV
-
-sites <- unique(MaumeeDV$site_no)
+
sites <- unique(MaumeeDV$site_no)
 dates <- sapply(sites, function(x) MaumeeDV$Date[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE)
 flow <- sapply(sites, function(x) MaumeeDV$Flow[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE)
 pH <- sapply(sites, function(x) MaumeeDV$pH_Median[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE)
@@ -108,13 +105,13 @@ 

0.2 Data manipulation

0.3 Simple timeseries

First, gsplot is used to create a simple timeseries graph for discharge, and a grid is added to help with data readability.

site <- '04193500'
-demoPlot <- gsplot() %>% 
+demoPlot <- gsplot(mgp=c(2.75, 0.3, 0.0)) %>% 
   lines(dates[[site]], flow[[site]], col="royalblue") %>%
   title(main=paste("Site", site), ylab="Flow, ft3/s") %>%
   grid()
 demoPlot
-Fig. 1 Simple flow timeseries using gsplot. +Fig. 1 Simple flow timeseries using gsplot.

Fig. 1 Simple flow timeseries using gsplot.

@@ -122,13 +119,16 @@

0.3 Simple timeseries

0.4 Simple timeseries using a log scale

This data may be better represented using a log scale due to the range of flow values. Thus, the yaxis is easily turned into a logged scale by inserting the code log='y'. To make sure that the grid lines correspond to the logged axis, the code equilogs=FALSE is used to let gridlines be drawn at unequal distances from each other.

site <- '04193500'
-demoPlot <- gsplot() %>% 
-  lines(dates[[site]], flow[[site]], col="royalblue", log='y') %>%
-  title(main=paste("Site", site), ylab="Flow, ft3/s") %>%
+options(scipen=5)
+demoPlot <- gsplot(mgp=c(3, 0.3, 0.0)) %>% 
+  lines(dates[[site]], flow[[site]], 
+        col="royalblue", log='y', 
+        ylab= expression(paste("Discharge in ",ft^3/s))) %>%
+  title(main=paste("Site", site)) %>%
   grid(equilogs=FALSE)
 demoPlot
-Fig. 2 Simple flow timeseries with a logged y-axis using gsplot. +Fig. 2 Simple flow timeseries with a logged y-axis using gsplot.

Fig. 2 Simple flow timeseries with a logged y-axis using gsplot.

@@ -151,7 +151,7 @@

0.5 Multiple plots in one figure<
plot2
plot3
-Fig. 3 (a) pH vs water temperature, (b) pH timeseries, (c) water temperature timeseries. +Fig. 3 (a) pH vs water temperature, (b) pH timeseries, (c) water temperature timeseries.

Fig. 3 (a) pH vs water temperature, (b) pH timeseries, (c) water temperature timeseries.

@@ -168,7 +168,7 @@

0.6 Compare timeseries of differe legend(location="below") demoPlot
-Fig. 4 Water temperature timeseries on primary y-axis with pH timeseries on secondary y-axis. +Fig. 4 Water temperature timeseries on primary y-axis with pH timeseries on secondary y-axis.

Fig. 4 Water temperature timeseries on primary y-axis with pH timeseries on secondary y-axis.

@@ -182,14 +182,14 @@

0.7 Adding to the plot retroactiv title(main=paste("Site", site), xlab='time', ylab='Water Temperature (deg C)') demoPlot
-Fig. 5 Initial plot of water temperature timeseries. +Fig. 5 Initial plot of water temperature timeseries.

Fig. 5 Initial plot of water temperature timeseries.

# notice the missing data from ~ 1991 through ~2011 and add a callout
 demoPlot <- callouts(demoPlot, x=as.Date("2000-01-01"), y=10,labels="Missing Data")
 demoPlot
-Fig. 6 Plot of water temperature timeseries with Missing Data callout retroactively added. +Fig. 6 Plot of water temperature timeseries with Missing Data callout retroactively added.

Fig. 6 Plot of water temperature timeseries with ‘Missing Data’ callout retroactively added.

diff --git a/vignettes/gsplotIntro.Rmd b/vignettes/gsplotIntro.Rmd index 3a99545..0a550a7 100644 --- a/vignettes/gsplotIntro.Rmd +++ b/vignettes/gsplotIntro.Rmd @@ -42,8 +42,6 @@ demoPlot Data from Maumee River will be used to showcase the workflow and features that `gsplot` offers. First, the data is manipulated to extract the timeseries as four separate variables - dates (formatted as yyyy-mm-dd), flow (discharge in cubic feet per second), pH, and Wtemp (water temperature in degrees Celcius). Additionally, the USGS site IDs for the sampling stations are identified. ```{r echo=TRUE, message=FALSE} -library(gsplot) -MaumeeDV <- MaumeeDV sites <- unique(MaumeeDV$site_no) dates <- sapply(sites, function(x) MaumeeDV$Date[which(MaumeeDV$site_no==x)], USE.NAMES=TRUE) @@ -60,7 +58,7 @@ First, `gsplot` is used to create a simple timeseries graph for discharge, and a ```{r echo=TRUE, fig.cap="Fig. 1 Simple flow timeseries using `gsplot`.", fig.width=6, fig.height=6} site <- '04193500' -demoPlot <- gsplot() %>% +demoPlot <- gsplot(mgp=c(2.75, 0.3, 0.0)) %>% lines(dates[[site]], flow[[site]], col="royalblue") %>% title(main=paste("Site", site), ylab="Flow, ft3/s") %>% grid() @@ -75,9 +73,12 @@ This data may be better represented using a log scale due to the range of flow v ```{r echo=TRUE, fig.cap="Fig. 2 Simple flow timeseries with a logged y-axis using `gsplot`.", fig.width=6, fig.height=6} site <- '04193500' -demoPlot <- gsplot() %>% - lines(dates[[site]], flow[[site]], col="royalblue", log='y') %>% - title(main=paste("Site", site), ylab="Flow, ft3/s") %>% +options(scipen=5) +demoPlot <- gsplot(mgp=c(3, 0.3, 0.0)) %>% + lines(dates[[site]], flow[[site]], + col="royalblue", log='y', + ylab= expression(paste("Discharge in ",ft^3/s))) %>% + title(main=paste("Site", site)) %>% grid(equilogs=FALSE) demoPlot From 32c72095c08f794e194c0c016e09abee7ddf009a Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 17:50:01 -0500 Subject: [PATCH 13/18] Integers. Probably need to think about other things. --- R/grid.R | 10 ++++++++-- man/grid.Rd | 6 ++++++ 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/R/grid.R b/R/grid.R index 7a8c62a..4799394 100644 --- a/R/grid.R +++ b/R/grid.R @@ -29,6 +29,12 @@ #' grid(side=c(1,2),col="green") %>% #' grid(side=c(3,4)) #' gs +#' +#' gs <- gsplot() %>% +#' points(x=seq.Date(as.Date("2000-01-01"),as.Date("2010-01-01"),length.out = 20), +#' y=1:20,axes=FALSE) %>% +#' grid() +#'gs grid <- function(object, ...) { override("graphics", "grid", object, ...) } @@ -51,7 +57,7 @@ draw_custom_grid <- function(object, index){ grid.args <- set_args("grid",object[[index]][['grid']], package = "graphics") - if(class(window$xlim) == "numeric"){ + if(class(window$xlim) %in% c("numeric","integer")){ x.at <- axTicks(view.info$x) } else if (class(window$xlim) == "Date"){ x.at <- axis.Date(view.info$x,window$xlim) @@ -67,7 +73,7 @@ draw_custom_grid <- function(object, index){ } } - if(class(window$ylim) == "numeric"){ + if(class(window$ylim) %in% c("numeric","integer")){ y.at <- axTicks(view.info$y) } else if (class(window$ylim) == "Date"){ y.at <- axis.Date(view.info$y,window$ylim) diff --git a/man/grid.Rd b/man/grid.Rd index 94c3758..9d009a5 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -37,5 +37,11 @@ gs <- gsplot() \%>\% grid(side=c(1,2),col="green") \%>\% grid(side=c(3,4)) gs + +gs <- gsplot() \%>\% + points(x=seq.Date(as.Date("2000-01-01"),as.Date("2010-01-01"),length.out = 20), + y=1:20,axes=FALSE) \%>\% + grid() +gs } From 09e8bd2c97b258a95d7d84f458a2acf710f2773b Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 22:14:44 -0500 Subject: [PATCH 14/18] That didn't need to be there. --- R/calc_views.R | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/R/calc_views.R b/R/calc_views.R index a7edde1..d588b04 100644 --- a/R/calc_views.R +++ b/R/calc_views.R @@ -38,11 +38,7 @@ group_views <- function(gsplot){ gsplot[[length(gsplot)]] <- NULL views <- views(gsplot) # existing non.views <- non_views(gsplot) - add_sides <- NULL - - if(is.list(tail.gs)){ - add_sides <- set_sides(tail.gs[['gs.config']][['side']]) - } + add_sides <- set_sides(tail.gs[['gs.config']][['side']]) if (!is.null(add_sides)){ to_draw <- setNames(list(c(tail.gs[['arguments']], legend.name=tail.gs[['gs.config']][['legend.name']])), tail.nm) From 5517e741b11668cf565e5c8717207fcfae137449 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 22:42:32 -0500 Subject: [PATCH 15/18] Fixes #206 Plenty of improvements could be made. --- NAMESPACE | 1 + R/gsplot-class.R | 32 +++++++++++++++++++++++++++++ man/summary.gsplot.Rd | 26 +++++++++++++++++++++++ tests/testthat/test-access_gsplot.R | 7 +++++++ 4 files changed, 66 insertions(+) create mode 100644 man/summary.gsplot.Rd diff --git a/NAMESPACE b/NAMESPACE index f9b97dc..142fe31 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,6 +3,7 @@ S3method(gsplot,default) S3method(logged,gsplot) S3method(print,gsplot) +S3method(summary,gsplot) S3method(xlim,gsplot) S3method(ylim,gsplot) export("%>%") diff --git a/R/gsplot-class.R b/R/gsplot-class.R index 746396e..ac90c73 100644 --- a/R/gsplot-class.R +++ b/R/gsplot-class.R @@ -26,3 +26,35 @@ gsplot.list <- function(x){ class(x) <- "gsplot" invisible(x) } + +#' Summary of gsplot object +#' +#' Summary information +#' +#' @param object list +#' @param \dots additional parameters +#' @export +#' @examples +#' gs <- gsplot() %>% +#' points(1:10,1:10) %>% +#' axis(side=1, at=seq(1,10,length.out=18),las=3) %>% +#' axis(side=3, labels=FALSE) %>% +#' grid(side=c(1,2),col="green") %>% +#' grid(side=c(3,4)) +#' summary(gs) +summary.gsplot <- function(object,...){ + + view.info <- view_info(object) + cat("Summary information of plotting object:\n") + cat(nrow(view.info),"views:\n") + for(i in seq_len(nrow(view.info))){ + cat("View:",i,"\nx side:", view.info$x[i], ",y side:", view.info$y[i], "\n") + cat("xlim:",as.numeric(xlim(object, side=view.info$x[i])[[1]]),",") + cat("ylim:",as.numeric(ylim(object, side=view.info$y[i])[[1]])) + if(view.info$log[i] != ""){ + cat(",log:",view.info$log[i]) + } + cat("\n") + } +} + diff --git a/man/summary.gsplot.Rd b/man/summary.gsplot.Rd new file mode 100644 index 0000000..4236d81 --- /dev/null +++ b/man/summary.gsplot.Rd @@ -0,0 +1,26 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/gsplot-class.R +\name{summary.gsplot} +\alias{summary.gsplot} +\title{Summary of gsplot object} +\usage{ +\method{summary}{gsplot}(object, ...) +} +\arguments{ +\item{object}{list} + +\item{\dots}{additional parameters} +} +\description{ +Summary information +} +\examples{ +gs <- gsplot() \%>\% + points(1:10,1:10) \%>\% + axis(side=1, at=seq(1,10,length.out=18),las=3) \%>\% + axis(side=3, labels=FALSE) \%>\% + grid(side=c(1,2),col="green") \%>\% + grid(side=c(3,4)) +summary(gs) +} + diff --git a/tests/testthat/test-access_gsplot.R b/tests/testthat/test-access_gsplot.R index 5456863..d759ed4 100644 --- a/tests/testthat/test-access_gsplot.R +++ b/tests/testthat/test-access_gsplot.R @@ -68,3 +68,10 @@ test_that("logged side extractor ",{ expect_equal(length(dual), 2) expect_true(all(dual)) }) + +test_that("summary ",{ + usrDef <- gsplot(mar=c(4,4,4,4), xaxs='r', yaxs='r') %>% + points(x=1, y=2, side=c(3,2), legend.name="Points 1", cex=3, xlab='cat',log='y') %>% + points(x=3:10,y=4:11, side=c(1,2), log='xy') + expect_output(summary(usrDef),regexp = "2 views:") +}) From 591803bf0c0ac941c79aa68adb66499f6a1852d0 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Mon, 12 Oct 2015 22:47:38 -0500 Subject: [PATCH 16/18] Add grid test. --- tests/testthat/tests-abline.R | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/tests/testthat/tests-abline.R b/tests/testthat/tests-abline.R index 4639f20..9560f87 100644 --- a/tests/testthat/tests-abline.R +++ b/tests/testthat/tests-abline.R @@ -47,4 +47,19 @@ test_that("arrows gsplot",{ s <- seq(length(x)-1) # one shorter than data gs = arrows(gs, x[s], y[s], x[s+1], y[s+1], col= 1:3) expect_equal(gs$view$arrows$col, 1:3) +}) + +test_that("grid",{ + plot(1:10) + grid() + + gs <- gsplot() %>% + points(1:10,1:10) %>% + axis(side=1, at=seq(1,10,length.out=18),las=3) %>% + axis(side=3, labels=FALSE) %>% + grid(side=c(1,2),col="green") %>% + grid(side=c(3,4)) + expect_equal(names(gs$view),c("points","grid","window")) + expect_equal(gs$view$grid$col,"green") + }) \ No newline at end of file From 6c312ede5c4be6aece68114a99aab0582f0adb27 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Tue, 13 Oct 2015 16:51:12 -0500 Subject: [PATCH 17/18] Update DESCRIPTION --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index a50379b..a9be48a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: gsplot Type: Package Title: Geological Survey Plotting -Version: 0.4.1 +Version: 0.4.2 Date: 2015-09-16 Authors@R: c( person("Jordan", "Read", role = "aut", email = "jread@usgs.gov"), From a89bfb498ff2df1711a60d9661d999f206abb9f4 Mon Sep 17 00:00:00 2001 From: Laura DeCicco Date: Wed, 14 Oct 2015 09:56:06 -0500 Subject: [PATCH 18/18] Fixed #274 --- R/grid.R | 14 ++++++++++---- man/grid.Rd | 8 +++++++- 2 files changed, 17 insertions(+), 5 deletions(-) diff --git a/R/grid.R b/R/grid.R index 4799394..09ba938 100644 --- a/R/grid.R +++ b/R/grid.R @@ -11,7 +11,7 @@ #' gsNew <- points(gs, y=1, x=2, xlim=c(0,NA),ylim=c(0,NA), #' col="blue", pch=18, legend.name="Points") #' gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines") -#' gsNew <- grid(gsNew, legend.name="Grid") +#' gsNew <- grid(gsNew) #' gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") #' gsNew <- legend(gsNew, location="topleft",title="Awesome!") #' gsNew @@ -34,7 +34,13 @@ #' points(x=seq.Date(as.Date("2000-01-01"),as.Date("2010-01-01"),length.out = 20), #' y=1:20,axes=FALSE) %>% #' grid() -#'gs +#' gs +#' +#' gs <- gsplot() %>% +#' points(x=1:10, y=1:10) %>% +#' grid(lty=3, col="gray") %>% +#' axis(side=2, reverse=TRUE) +#' gs grid <- function(object, ...) { override("graphics", "grid", object, ...) } @@ -68,7 +74,7 @@ draw_custom_grid <- function(object, index){ if(view.info$x.side.defined.by.user){ axes.index <- i[definded.sides == view.info$x] x <- object[axes.index][['axis']][['arguments']][['at']] - if(length(x.at) != 0){ + if(!is.null(x)){ x.at <-x } } @@ -84,7 +90,7 @@ draw_custom_grid <- function(object, index){ if(view.info$y.side.defined.by.user){ axes.index <- i[definded.sides == view.info$y] y <- object[axes.index][['axis']][['arguments']][['at']] - if(length(y.at) != 0){ + if(!is.null(y)){ y.at <- y } } diff --git a/man/grid.Rd b/man/grid.Rd index 9d009a5..b44d875 100644 --- a/man/grid.Rd +++ b/man/grid.Rd @@ -19,7 +19,7 @@ gs <- gsplot() gsNew <- points(gs, y=1, x=2, xlim=c(0,NA),ylim=c(0,NA), col="blue", pch=18, legend.name="Points") gsNew <- lines(gsNew, c(3,4,3), c(2,4,6), legend.name="Lines") -gsNew <- grid(gsNew, legend.name="Grid") +gsNew <- grid(gsNew) gsNew <- abline(gsNew, b=1, a=0, legend.name="1:1") gsNew <- legend(gsNew, location="topleft",title="Awesome!") gsNew @@ -43,5 +43,11 @@ gs <- gsplot() \%>\% y=1:20,axes=FALSE) \%>\% grid() gs + +gs <- gsplot() \%>\% + points(x=1:10, y=1:10) \%>\% + grid(lty=3, col="gray") \%>\% + axis(side=2, reverse=TRUE) +gs }