@@ -98,6 +98,44 @@ wbt_breach_depressions <- function(dem, output, max_depth=NULL, max_length=NULL,
9898}
9999
100100
101+ # ' Breach depressions least cost
102+ # '
103+ # ' Breaches the depressions in a DEM using a least-cost pathway method.
104+ # '
105+ # ' @param dem Input raster DEM file.
106+ # ' @param output Output raster file.
107+ # ' @param radius .
108+ # ' @param max_cost Optional maximum breach cost (default is Inf).
109+ # ' @param min_dist Optional flag indicating whether to minimize breach distances.
110+ # ' @param flat_increment Optional elevation increment applied to flat areas.
111+ # ' @param fill Optional flag indicating whether to fill any remaining unbreached depressions.
112+ # ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
113+ # '
114+ # ' @return Returns the tool text outputs.
115+ # ' @export
116+ wbt_breach_depressions_least_cost <- function (dem , output , radius , max_cost = NULL , min_dist = TRUE , flat_increment = NULL , fill = TRUE , verbose_mode = FALSE ) {
117+ wbt_init()
118+ args <- " "
119+ args <- paste(args , paste0(" --dem=" , dem ))
120+ args <- paste(args , paste0(" --output=" , output ))
121+ args <- paste(args , paste0(" --radius=" , radius ))
122+ if (! is.null(max_cost )) {
123+ args <- paste(args , paste0(" --max_cost=" , max_cost ))
124+ }
125+ if (min_dist ) {
126+ args <- paste(args , " --min_dist" )
127+ }
128+ if (! is.null(flat_increment )) {
129+ args <- paste(args , paste0(" --flat_increment=" , flat_increment ))
130+ }
131+ if (fill ) {
132+ args <- paste(args , " --fill" )
133+ }
134+ tool_name <- as.character(match.call()[[1 ]])
135+ wbt_run_tool(tool_name , args , verbose_mode )
136+ }
137+
138+
101139# ' Breach single cell pits
102140# '
103141# ' Removes single-cell pits from an input DEM by breaching.
@@ -118,6 +156,34 @@ wbt_breach_single_cell_pits <- function(dem, output, verbose_mode=FALSE) {
118156}
119157
120158
159+ # ' Burn streams at roads
160+ # '
161+ # ' Burns-in streams at the sites of road embankments.
162+ # '
163+ # ' @param dem Input raster digital elevation model (DEM) file.
164+ # ' @param streams Input vector streams file.
165+ # ' @param roads Input vector roads file.
166+ # ' @param output Output raster file.
167+ # ' @param width Maximum road embankment width, in map units.
168+ # ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
169+ # '
170+ # ' @return Returns the tool text outputs.
171+ # ' @export
172+ wbt_burn_streams_at_roads <- function (dem , streams , roads , output , width = NULL , verbose_mode = FALSE ) {
173+ wbt_init()
174+ args <- " "
175+ args <- paste(args , paste0(" --dem=" , dem ))
176+ args <- paste(args , paste0(" --streams=" , streams ))
177+ args <- paste(args , paste0(" --roads=" , roads ))
178+ args <- paste(args , paste0(" --output=" , output ))
179+ if (! is.null(width )) {
180+ args <- paste(args , paste0(" --width=" , width ))
181+ }
182+ tool_name <- as.character(match.call()[[1 ]])
183+ wbt_run_tool(tool_name , args , verbose_mode )
184+ }
185+
186+
121187# ' D8 flow accumulation
122188# '
123189# ' Calculates a D8 flow accumulation raster from an input DEM.
@@ -494,11 +560,43 @@ wbt_fill_burn <- function(dem, streams, output, verbose_mode=FALSE) {
494560# ' @param output Output raster file.
495561# ' @param fix_flats Optional flag indicating whether flat areas should have a small gradient applied.
496562# ' @param flat_increment Optional elevation increment applied to flat areas.
563+ # ' @param max_depth Optional maximum depression depth to fill.
564+ # ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
565+ # '
566+ # ' @return Returns the tool text outputs.
567+ # ' @export
568+ wbt_fill_depressions <- function (dem , output , fix_flats = TRUE , flat_increment = NULL , max_depth = NULL , verbose_mode = FALSE ) {
569+ wbt_init()
570+ args <- " "
571+ args <- paste(args , paste0(" --dem=" , dem ))
572+ args <- paste(args , paste0(" --output=" , output ))
573+ if (fix_flats ) {
574+ args <- paste(args , " --fix_flats" )
575+ }
576+ if (! is.null(flat_increment )) {
577+ args <- paste(args , paste0(" --flat_increment=" , flat_increment ))
578+ }
579+ if (! is.null(max_depth )) {
580+ args <- paste(args , paste0(" --max_depth=" , max_depth ))
581+ }
582+ tool_name <- as.character(match.call()[[1 ]])
583+ wbt_run_tool(tool_name , args , verbose_mode )
584+ }
585+
586+
587+ # ' Fill depressions wang and lui
588+ # '
589+ # ' Fills all of the depressions in a DEM. Depression breaching should be preferred in most cases.
590+ # '
591+ # ' @param dem Input raster DEM file.
592+ # ' @param output Output raster file.
593+ # ' @param fix_flats Optional flag indicating whether flat areas should have a small gradient applied.
594+ # ' @param flat_increment Optional elevation increment applied to flat areas.
497595# ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
498596# '
499597# ' @return Returns the tool text outputs.
500598# ' @export
501- wbt_fill_depressions <- function (dem , output , fix_flats = TRUE , flat_increment = NULL , verbose_mode = FALSE ) {
599+ wbt_fill_depressions_wang_and_lui <- function (dem , output , fix_flats = TRUE , flat_increment = NULL , verbose_mode = FALSE ) {
502600 wbt_init()
503601 args <- " "
504602 args <- paste(args , paste0(" --dem=" , dem ))
@@ -900,17 +998,17 @@ wbt_rho8_pointer <- function(dem, output, esri_pntr=FALSE, verbose_mode=FALSE) {
900998# '
901999# ' Identifies the depressions in a DEM, giving each feature a unique identifier.
9021000# '
903- # ' @param dem Input raster DEM file.
1001+ # ' @param input Input raster DEM file.
9041002# ' @param output Output raster file.
9051003# ' @param zero_background Flag indicating whether a background value of zero should be used.
9061004# ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
9071005# '
9081006# ' @return Returns the tool text outputs.
9091007# ' @export
910- wbt_sink <- function (dem , output , zero_background = FALSE , verbose_mode = FALSE ) {
1008+ wbt_sink <- function (input , output , zero_background = FALSE , verbose_mode = FALSE ) {
9111009 wbt_init()
9121010 args <- " "
913- args <- paste(args , paste0(" --dem =" , dem ))
1011+ args <- paste(args , paste0(" --input =" , input ))
9141012 args <- paste(args , paste0(" --output=" , output ))
9151013 if (zero_background ) {
9161014 args <- paste(args , " --zero_background" )
@@ -1080,6 +1178,26 @@ wbt_unnest_basins <- function(d8_pntr, pour_pts, output, esri_pntr=FALSE, verbos
10801178}
10811179
10821180
1181+ # ' Upslope depression storage
1182+ # '
1183+ # ' Estimates the average upslope depression storage depth.
1184+ # '
1185+ # ' @param dem Input raster DEM file.
1186+ # ' @param output Output raster file.
1187+ # ' @param verbose_mode Sets verbose mode. If verbose mode is False, tools will not print output messages.
1188+ # '
1189+ # ' @return Returns the tool text outputs.
1190+ # ' @export
1191+ wbt_upslope_depression_storage <- function (dem , output , verbose_mode = FALSE ) {
1192+ wbt_init()
1193+ args <- " "
1194+ args <- paste(args , paste0(" --dem=" , dem ))
1195+ args <- paste(args , paste0(" --output=" , output ))
1196+ tool_name <- as.character(match.call()[[1 ]])
1197+ wbt_run_tool(tool_name , args , verbose_mode )
1198+ }
1199+
1200+
10831201# ' Watershed
10841202# '
10851203# ' Identifies the watershed, or drainage basin, draining to a set of target cells.
0 commit comments