Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-17 Thread Bhagwat, Aditya
Owkies, will file a PR in one of the coming days. And continue the discussion 
when I do so.

Cheers!

Aditya


From: Stuart Lee [le...@wehi.edu.au]
Sent: Tuesday, September 17, 2019 5:33 AM
To: Michael Lawrence
Cc: Bhagwat, Aditya; bioc-devel@r-project.org
Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

Hi Aditya,

I think straddle would be a great addition to plyranges. Happy for you to put 
in a PR and add you as a contributor.

Maybe instead of specifying the start etc. we could dispatch on anchored ranges 
instead? So we�d follow the anchor_start(gr) %>% straddle(). We could also have 
the directed version for considering strands.

https://github.com/sa-lee/plyranges

Thanks,
Stuart

---
Stuart Lee
Visiting PhD Student - Ritchie Lab



On 13 Sep 2019, at 22:38, Michael Lawrence 
mailto:lawrence.mich...@gene.com>> wrote:

Thanks for these suggestions; I think they're worth considering.

I've never been totally satisfied with (my function) flank(), because
it's limited and its arguments are somewhat obscure in meaning. You
can check out what we did in plyranges:
https://rdrr.io/bioc/plyranges/man/flank-ranges.html. Your functions
are more flexible, because they are two-way about the endpoint, like
promoters(). Sometimes I've solved that with resize(flank()), but
that's not ideal.  Maybe a better name is "straddle" for when ranges
straddle one of the endpoints? In keeping with the current pattern of
Ranges API, there would be a single function: straddle(x, side, left,
right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
be like promoters(x, 100, 10) for a positive or "*" strand range. That
brings up strandedness, which needs to be considered here. For
unstranded ranges, it may be that direct start() and end()
manipulation is actually more transparent than a special verb. I
wonder what Stuart Lee thinks?

The functions that involve reduce() wouldn't fit into the intrarange
operations, as they are summarizing ranges, not transforming them.
They may be going too far.

Michael

On Fri, Sep 13, 2019 at 4:48 AM Bhagwat, Aditya
mailto:aditya.bhag...@mpi-bn.mpg.de>> wrote:

Dear bioc-devel,

The ?GenomicRanges::`intra-range-methods` are very useful for range 
arithmetic<https://genomicsclass.github.io/book/pages/figure/bioc1_igranges-unnamed-chunk-6-1.png>

Feedback request: would it be of general use to add the methods below to the 
GenomicRanges::`intra-range-methods` palette (after properly S4-ing them)?
Or shall I keep them in 
multicrispr<https://gitlab.gwdg.de/loosolab/software/multicrispr>?
Additional feedback welcome as well (e.g. re-implementation of already existing 
functionality).


1) Left flank

#' Left flank
#' @param gr   \code{\link[GenomicRanges]{GRanges-class}}
#' @param leftstart number: flank start (relative to range start)
#' @param leftend   number: flank end   (relative to range start)
#' @return a \code{\link[GenomicRanges]{GRanges-class}}
#' @export
#' @examples
#' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
#' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
#' gr <- read_bed(bedfile, bsgenome)
#' left_flank(gr)
left_flank <- function(gr, leftstart = -200, leftend   = -1){

   # Assert
   assert_is_identical_to_true(is(gr, 'GRanges'))
   assert_is_a_number(leftstart)
   assert_is_a_number(leftend)

   # Flank
   newranges <- gr
   end(newranges)   <- start(gr) + leftend
   start(newranges) <- start(gr) + leftstart

   # Return
   newranges
}


2) Right flank

#' Right flank
#' @param gr\code{\link[GenomicRanges]{GRanges-class}}
#' @param rightstart number: flank start (relative to range end)
#' @param rightend   number: flank end   (relative to range end)
#' @return \code{\link[GenomicRanges]{GRanges-class}}
#' @export
#' @examples
#' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
#' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
#' gr <- read_bed(bedfile, bsgenome)
#' right_flank(gr)
#' @export
right_flank <- function(gr, rightstart = 1, rightend   = 200){

   # Assert
   assert_is_identical_to_true(is(gr, 'GRanges'))
   assert_is_a_number(rightstart)
   assert_is_a_number(rightend)
   assert_is_a_bool(verbose)

   # Flank
   newranges <- gr
   start(newranges) <- end(newranges) + rightstart
   end(newranges)   <- end(newranges) + rightend

   # Plot
   if (plot)  plot_intervals(GRangesList(sites = gr, rightflanks = newranges))

   # Return
   cmessage('\t\t%d right flanks : [end%s%d, end%s%d]',
   length(newranges),
   csign(rightstart),
   abs(rightstart),
   csign(rightend),
   abs(rightend))
   newranges
}


3) Slop

#' Slop (i.e. extend left/right)
#' @param gr\code{\link[GenomicRanges]{GRanges-class}}
#' @param leftstart number: flank start (relative to range start)
#' @param righte

Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-16 Thread Stuart Lee
Hi Aditya,

I think straddle would be a great addition to plyranges. Happy for you to put 
in a PR and add you as a contributor.

Maybe instead of specifying the start etc. we could dispatch on anchored ranges 
instead? So we’d follow the anchor_start(gr) %>% straddle(). We could also have 
the directed version for considering strands.

https://github.com/sa-lee/plyranges

Thanks,
Stuart

---
Stuart Lee
Visiting PhD Student - Ritchie Lab



On 13 Sep 2019, at 22:38, Michael Lawrence 
mailto:lawrence.mich...@gene.com>> wrote:

Thanks for these suggestions; I think they're worth considering.

I've never been totally satisfied with (my function) flank(), because
it's limited and its arguments are somewhat obscure in meaning. You
can check out what we did in plyranges:
https://rdrr.io/bioc/plyranges/man/flank-ranges.html. Your functions
are more flexible, because they are two-way about the endpoint, like
promoters(). Sometimes I've solved that with resize(flank()), but
that's not ideal.  Maybe a better name is "straddle" for when ranges
straddle one of the endpoints? In keeping with the current pattern of
Ranges API, there would be a single function: straddle(x, side, left,
right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
be like promoters(x, 100, 10) for a positive or "*" strand range. That
brings up strandedness, which needs to be considered here. For
unstranded ranges, it may be that direct start() and end()
manipulation is actually more transparent than a special verb. I
wonder what Stuart Lee thinks?

The functions that involve reduce() wouldn't fit into the intrarange
operations, as they are summarizing ranges, not transforming them.
They may be going too far.

Michael

On Fri, Sep 13, 2019 at 4:48 AM Bhagwat, Aditya
mailto:aditya.bhag...@mpi-bn.mpg.de>> wrote:

Dear bioc-devel,

The ?GenomicRanges::`intra-range-methods` are very useful for range 
arithmetic

Feedback request: would it be of general use to add the methods below to the 
GenomicRanges::`intra-range-methods` palette (after properly S4-ing them)?
Or shall I keep them in 
multicrispr?
Additional feedback welcome as well (e.g. re-implementation of already existing 
functionality).


1) Left flank

#' Left flank
#' @param gr   \code{\link[GenomicRanges]{GRanges-class}}
#' @param leftstart number: flank start (relative to range start)
#' @param leftend   number: flank end   (relative to range start)
#' @return a \code{\link[GenomicRanges]{GRanges-class}}
#' @export
#' @examples
#' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
#' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
#' gr <- read_bed(bedfile, bsgenome)
#' left_flank(gr)
left_flank <- function(gr, leftstart = -200, leftend   = -1){

   # Assert
   assert_is_identical_to_true(is(gr, 'GRanges'))
   assert_is_a_number(leftstart)
   assert_is_a_number(leftend)

   # Flank
   newranges <- gr
   end(newranges)   <- start(gr) + leftend
   start(newranges) <- start(gr) + leftstart

   # Return
   newranges
}


2) Right flank

#' Right flank
#' @param gr\code{\link[GenomicRanges]{GRanges-class}}
#' @param rightstart number: flank start (relative to range end)
#' @param rightend   number: flank end   (relative to range end)
#' @return \code{\link[GenomicRanges]{GRanges-class}}
#' @export
#' @examples
#' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
#' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
#' gr <- read_bed(bedfile, bsgenome)
#' right_flank(gr)
#' @export
right_flank <- function(gr, rightstart = 1, rightend   = 200){

   # Assert
   assert_is_identical_to_true(is(gr, 'GRanges'))
   assert_is_a_number(rightstart)
   assert_is_a_number(rightend)
   assert_is_a_bool(verbose)

   # Flank
   newranges <- gr
   start(newranges) <- end(newranges) + rightstart
   end(newranges)   <- end(newranges) + rightend

   # Plot
   if (plot)  plot_intervals(GRangesList(sites = gr, rightflanks = newranges))

   # Return
   cmessage('\t\t%d right flanks : [end%s%d, end%s%d]',
   length(newranges),
   csign(rightstart),
   abs(rightstart),
   csign(rightend),
   abs(rightend))
   newranges
}


3) Slop

#' Slop (i.e. extend left/right)
#' @param gr\code{\link[GenomicRanges]{GRanges-class}}
#' @param leftstart number: flank start (relative to range start)
#' @param rightend  number: flank end   (relative to range end)
#' @return \code{\link[GenomicRanges]{GRanges-class}}
#' @export
#' @examples
#' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
#' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
#' gr <- read_bed(bedfile, bsgenome)
#' slop(gr)
#' @export
slop <- function(gr, leftstart = -22, rightend  =  22){

   # Assert
   assert_is_identical_to_true(methods::is(gr, 'GRanges'))
   assert_is_a_number(leftstart)
 

Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-16 Thread Michael Lawrence via Bioc-devel
It's on the right track. The case where two ranges are produced is
problematic, because we would want this to be a parallel vector
operation, where the length of the input is the same as the length of
the output. So that last case I think might just ignore the leftend
and rightstart arguments with a warning, returning a result with the
gap filled.

Michael

On Mon, Sep 16, 2019 at 1:48 AM Bhagwat, Aditya
 wrote:
>
> Michael, actually, such a generic straddle() could be useful:
>
> straddle(leftstart=-100, rightend=100)  # extended range
> straddle(leftstart=-100, leftend=-1)   # left flank
> straddle(rightstart=1, rightend=100) # right flank
> straddle(leftstart=-100, leftend=-1, rightstart=1, rightend=100) # left and 
> right flanks
>
> What do you think?
>
> Aditya
>
> 
> From: Bioc-devel [bioc-devel-boun...@r-project.org] on behalf of Bhagwat, 
> Aditya [aditya.bhag...@mpi-bn.mpg.de]
> Sent: Monday, September 16, 2019 10:30 AM
> To: Michael Lawrence
> Cc: bioc-devel@r-project.org
> Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`
>
> Hmm no that wouldn't work, it would become messy trying to figure out when 
> incompatible arguments are provided.
>
> Aditya
>
>
> 
> From: Bioc-devel [bioc-devel-boun...@r-project.org] on behalf of Bhagwat, 
> Aditya [aditya.bhag...@mpi-bn.mpg.de]
> Sent: Monday, September 16, 2019 10:09 AM
> To: Michael Lawrence
> Cc: bioc-devel@r-project.org
> Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`
>
> Hi Michael,
>
> Thank you for the pointer to plyranges - looks very useful!
>
> > Maybe a better name is "straddle" for when ranges
> > straddle one of the endpoints? In keeping with the current pattern of
> > Ranges API, there would be a single function: straddle(x, side, left,
> > right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
> > be like promoters(x, 100, 10) for a positive or "*" strand range.
>
> Cool suggestion, and a really fitting verb :-)
> Just slightly modifying your suggestion makes the API fully generic (waaw!), 
> generalizing over left_flank, right_flank, as well as slop:
>
> straddle(leftstart, leftend, rightstart, rightend)
>
> Would it be worth having such functionality in GenomicRanges or plyranges, 
> rather than multicrispr<https://gitlab.gwdg.de/loosolab/software/multicrispr>?
>
>
> > That brings up strandedness, which needs to be considered here. For
> > unstranded ranges, it may be that direct start() and end()
> > manipulation is actually more transparent than a special verb.
>
> I ended up using left/right for unstranded, and up/down for stranded 
> operations.
>
>
> > The functions that involve reduce() wouldn't fit into the intrarange
> > operations, as they are summarizing ranges, not transforming them.
> > They may be going too far.
>
> True. Actually, the functions would be cleaner without the reduce(), I think 
> I'll take that out.
>
> Cheers,
>
> Aditya
>
>
> [[alternative HTML version deleted]]
>
> ___
> Bioc-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/bioc-devel
>
> ___
> Bioc-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/bioc-devel



-- 
Michael Lawrence
Scientist, Bioinformatics and Computational Biology
Genentech, A Member of the Roche Group
Office +1 (650) 225-7760
micha...@gene.com

Join Genentech on LinkedIn | Twitter | Facebook | Instagram | YouTube

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel


Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-16 Thread Bhagwat, Aditya
Michael, actually, such a generic straddle() could be useful:

straddle(leftstart=-100, rightend=100)  # extended range
straddle(leftstart=-100, leftend=-1)   # left flank
straddle(rightstart=1, rightend=100) # right flank
straddle(leftstart=-100, leftend=-1, rightstart=1, rightend=100) # left and 
right flanks

What do you think?

Aditya


From: Bioc-devel [bioc-devel-boun...@r-project.org] on behalf of Bhagwat, 
Aditya [aditya.bhag...@mpi-bn.mpg.de]
Sent: Monday, September 16, 2019 10:30 AM
To: Michael Lawrence
Cc: bioc-devel@r-project.org
Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

Hmm no that wouldn't work, it would become messy trying to figure out when 
incompatible arguments are provided.

Aditya



From: Bioc-devel [bioc-devel-boun...@r-project.org] on behalf of Bhagwat, 
Aditya [aditya.bhag...@mpi-bn.mpg.de]
Sent: Monday, September 16, 2019 10:09 AM
To: Michael Lawrence
Cc: bioc-devel@r-project.org
Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

Hi Michael,

Thank you for the pointer to plyranges - looks very useful!

> Maybe a better name is "straddle" for when ranges
> straddle one of the endpoints? In keeping with the current pattern of
> Ranges API, there would be a single function: straddle(x, side, left,
> right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
> be like promoters(x, 100, 10) for a positive or "*" strand range.

Cool suggestion, and a really fitting verb :-)
Just slightly modifying your suggestion makes the API fully generic (waaw!), 
generalizing over left_flank, right_flank, as well as slop:

straddle(leftstart, leftend, rightstart, rightend)

Would it be worth having such functionality in GenomicRanges or plyranges, 
rather than multicrispr<https://gitlab.gwdg.de/loosolab/software/multicrispr>?


> That brings up strandedness, which needs to be considered here. For
> unstranded ranges, it may be that direct start() and end()
> manipulation is actually more transparent than a special verb.

I ended up using left/right for unstranded, and up/down for stranded operations.


> The functions that involve reduce() wouldn't fit into the intrarange
> operations, as they are summarizing ranges, not transforming them.
> They may be going too far.

True. Actually, the functions would be cleaner without the reduce(), I think 
I'll take that out.

Cheers,

Aditya


[[alternative HTML version deleted]]

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel

[[alternative HTML version deleted]]

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel


Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-16 Thread Bhagwat, Aditya
Hmm no that wouldn't work, it would become messy trying to figure out when 
incompatible arguments are provided. 

Aditya



From: Bioc-devel [bioc-devel-boun...@r-project.org] on behalf of Bhagwat, 
Aditya [aditya.bhag...@mpi-bn.mpg.de]
Sent: Monday, September 16, 2019 10:09 AM
To: Michael Lawrence
Cc: bioc-devel@r-project.org
Subject: Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

Hi Michael,

Thank you for the pointer to plyranges - looks very useful!

> Maybe a better name is "straddle" for when ranges
> straddle one of the endpoints? In keeping with the current pattern of
> Ranges API, there would be a single function: straddle(x, side, left,
> right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
> be like promoters(x, 100, 10) for a positive or "*" strand range.

Cool suggestion, and a really fitting verb :-)
Just slightly modifying your suggestion makes the API fully generic (waaw!), 
generalizing over left_flank, right_flank, as well as slop:

straddle(leftstart, leftend, rightstart, rightend)

Would it be worth having such functionality in GenomicRanges or plyranges, 
rather than multicrispr<https://gitlab.gwdg.de/loosolab/software/multicrispr>?


> That brings up strandedness, which needs to be considered here. For
> unstranded ranges, it may be that direct start() and end()
> manipulation is actually more transparent than a special verb.

I ended up using left/right for unstranded, and up/down for stranded operations.


> The functions that involve reduce() wouldn't fit into the intrarange
> operations, as they are summarizing ranges, not transforming them.
> They may be going too far.

True. Actually, the functions would be cleaner without the reduce(), I think 
I'll take that out.

Cheers,

Aditya


[[alternative HTML version deleted]]

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel


Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-16 Thread Bhagwat, Aditya
Hi Michael,

Thank you for the pointer to plyranges - looks very useful!

> Maybe a better name is "straddle" for when ranges
> straddle one of the endpoints? In keeping with the current pattern of
> Ranges API, there would be a single function: straddle(x, side, left,
> right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
> be like promoters(x, 100, 10) for a positive or "*" strand range.

Cool suggestion, and a really fitting verb :-)
Just slightly modifying your suggestion makes the API fully generic (waaw!), 
generalizing over left_flank, right_flank, as well as slop:

straddle(leftstart, leftend, rightstart, rightend)

Would it be worth having such functionality in GenomicRanges or plyranges, 
rather than multicrispr?


> That brings up strandedness, which needs to be considered here. For
> unstranded ranges, it may be that direct start() and end()
> manipulation is actually more transparent than a special verb.

I ended up using left/right for unstranded, and up/down for stranded operations.


> The functions that involve reduce() wouldn't fit into the intrarange
> operations, as they are summarizing ranges, not transforming them.
> They may be going too far.

True. Actually, the functions would be cleaner without the reduce(), I think 
I'll take that out.

Cheers,

Aditya


[[alternative HTML version deleted]]

___
Bioc-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/bioc-devel


Re: [Bioc-devel] Extending GenomicRanges::`intra-range-methods`

2019-09-13 Thread Michael Lawrence via Bioc-devel
Thanks for these suggestions; I think they're worth considering.

I've never been totally satisfied with (my function) flank(), because
it's limited and its arguments are somewhat obscure in meaning. You
can check out what we did in plyranges:
https://rdrr.io/bioc/plyranges/man/flank-ranges.html. Your functions
are more flexible, because they are two-way about the endpoint, like
promoters(). Sometimes I've solved that with resize(flank()), but
that's not ideal.  Maybe a better name is "straddle" for when ranges
straddle one of the endpoints? In keeping with the current pattern of
Ranges API, there would be a single function: straddle(x, side, left,
right, ignore.strand=FALSE). So straddle(x, "start", -100, 10) would
be like promoters(x, 100, 10) for a positive or "*" strand range. That
brings up strandedness, which needs to be considered here. For
unstranded ranges, it may be that direct start() and end()
manipulation is actually more transparent than a special verb. I
wonder what Stuart Lee thinks?

The functions that involve reduce() wouldn't fit into the intrarange
operations, as they are summarizing ranges, not transforming them.
They may be going too far.

Michael

On Fri, Sep 13, 2019 at 4:48 AM Bhagwat, Aditya
 wrote:
>
> Dear bioc-devel,
>
> The ?GenomicRanges::`intra-range-methods` are very useful for range 
> arithmetic
>
> Feedback request: would it be of general use to add the methods below to the 
> GenomicRanges::`intra-range-methods` palette (after properly S4-ing them)?
> Or shall I keep them in 
> multicrispr?
> Additional feedback welcome as well (e.g. re-implementation of already 
> existing functionality).
>
>
> 1) Left flank
>
> #' Left flank
> #' @param gr   \code{\link[GenomicRanges]{GRanges-class}}
> #' @param leftstart number: flank start (relative to range start)
> #' @param leftend   number: flank end   (relative to range start)
> #' @return a \code{\link[GenomicRanges]{GRanges-class}}
> #' @export
> #' @examples
> #' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
> #' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
> #' gr <- read_bed(bedfile, bsgenome)
> #' left_flank(gr)
> left_flank <- function(gr, leftstart = -200, leftend   = -1){
>
> # Assert
> assert_is_identical_to_true(is(gr, 'GRanges'))
> assert_is_a_number(leftstart)
> assert_is_a_number(leftend)
>
> # Flank
> newranges <- gr
> end(newranges)   <- start(gr) + leftend
> start(newranges) <- start(gr) + leftstart
>
> # Return
> newranges
> }
>
>
> 2) Right flank
>
> #' Right flank
> #' @param gr\code{\link[GenomicRanges]{GRanges-class}}
> #' @param rightstart number: flank start (relative to range end)
> #' @param rightend   number: flank end   (relative to range end)
> #' @return \code{\link[GenomicRanges]{GRanges-class}}
> #' @export
> #' @examples
> #' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
> #' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
> #' gr <- read_bed(bedfile, bsgenome)
> #' right_flank(gr)
> #' @export
> right_flank <- function(gr, rightstart = 1, rightend   = 200){
>
> # Assert
> assert_is_identical_to_true(is(gr, 'GRanges'))
> assert_is_a_number(rightstart)
> assert_is_a_number(rightend)
> assert_is_a_bool(verbose)
>
> # Flank
> newranges <- gr
> start(newranges) <- end(newranges) + rightstart
> end(newranges)   <- end(newranges) + rightend
>
> # Plot
> if (plot)  plot_intervals(GRangesList(sites = gr, rightflanks = 
> newranges))
>
> # Return
> cmessage('\t\t%d right flanks : [end%s%d, end%s%d]',
> length(newranges),
> csign(rightstart),
> abs(rightstart),
> csign(rightend),
> abs(rightend))
> newranges
> }
>
>
> 3) Slop
>
> #' Slop (i.e. extend left/right)
> #' @param gr\code{\link[GenomicRanges]{GRanges-class}}
> #' @param leftstart number: flank start (relative to range start)
> #' @param rightend  number: flank end   (relative to range end)
> #' @return \code{\link[GenomicRanges]{GRanges-class}}
> #' @export
> #' @examples
> #' bedfile <- system.file('extdata/SRF.bed', package = 'multicrispr')
> #' bsgenome <- BSgenome.Mmusculus.UCSC.mm10::Mmusculus
> #' gr <- read_bed(bedfile, bsgenome)
> #' slop(gr)
> #' @export
> slop <- function(gr, leftstart = -22, rightend  =  22){
>
> # Assert
> assert_is_identical_to_true(methods::is(gr, 'GRanges'))
> assert_is_a_number(leftstart)
> assert_is_a_number(rightend)
> assert_is_a_bool(verbose)
>
> # Slop
> newranges <- gr
> start(newranges) <- start(newranges) + leftstart
> end(newranges)   <- end(newranges)   + rightend
>
> # Return
> newranges
> }
>
>
> 4) Flank fourways
>
> #' Flank fourways
> #'
> #' Flank left and right, for both