Skip to content

Commit

Permalink
tests
Browse files Browse the repository at this point in the history
  • Loading branch information
trafficonese committed Aug 21, 2024
1 parent e50e166 commit d8333df
Show file tree
Hide file tree
Showing 2 changed files with 248 additions and 0 deletions.
124 changes: 124 additions & 0 deletions tests/testthat/test-groupedlayerscontrol.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,124 @@
library(testthat)
library(leaflet)
library(leaflet.extras)

test_that("Test addGroupedLayersControl", {
# Basic functionality
ts <- leaflet() %>%
addTiles(group = "OpenStreetMap") %>%
addProviderTiles("CartoDB", group = "CartoDB") %>%
addCircleMarkers(runif(20, -75, -74), runif(20, 41, 42), color = "red", group = "Markers2") %>%
addCircleMarkers(runif(20, -75, -74), runif(20, 41, 42), color = "green", group = "Markers1") %>%
addGroupedLayersControl(
baseGroups = c("OpenStreetMap", "CartoDB"),
overlayGroups = list(
"Layergroup_2" = c("Markers5", "Markers4"),
"Layergroup_1" = c("Markers2", "Markers1", "Markers3")),
position = "topright",
options = groupedLayersControlOptions(groupCheckboxes = TRUE, collapsed = FALSE)
)
expect_s3_class(ts, "leaflet")
expect_true(any(sapply(ts$dependencies, function(dep) dep$name == "lfx-groupedlayercontrol")))
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "addGroupedLayersControl")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[1]], c("OpenStreetMap", "CartoDB"))

# Basic functionality
ts <- leaflet() %>%
addTiles(group = "OpenStreetMap") %>%
addProviderTiles("CartoDB", group = "CartoDB") %>%
addCircleMarkers(runif(20, -75, -74), runif(20, 41, 42), color = "red", group = "Markers2") %>%
addCircleMarkers(runif(20, -75, -74), runif(20, 41, 42), color = "green", group = "Markers1") %>%
addGroupedLayersControl(
baseGroups = c("OpenStreetMap", "CartoDB"),
overlayGroups = list(
"Layergroup_2" = c("Markername5" = "Markers5", "Markername4" = "Markers4"),
"Layergroup_1" = c("Markername2" = "Markers2", "Markername1" = "Markers1",
"Markername3" = "Markers3")),
position = "topright",
options = groupedLayersControlOptions(groupCheckboxes = TRUE, collapsed = FALSE)
)
expect_s3_class(ts, "leaflet")
expect_true(any(sapply(ts$dependencies, function(dep) dep$name == "lfx-groupedlayercontrol")))
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "addGroupedLayersControl")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[1]], c("OpenStreetMap", "CartoDB"))

# Using different positions
positions <- c("topright", "bottomright", "bottomleft", "topleft")
for (pos in positions) {
ts <- leaflet() %>%
addGroupedLayersControl(position = pos)
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[3]]$position, pos)
}

# Options check
ts <- leaflet() %>%
addGroupedLayersControl(options = groupedLayersControlOptions(
exclusiveGroups = "Layergroup_1",
groupCheckboxes = FALSE,
collapsed = TRUE
))
expect_s3_class(ts, "leaflet")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[3]]$exclusiveGroups, "Layergroup_1")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[3]]$groupCheckboxes, FALSE)
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[3]]$collapsed, TRUE)

## Test groupedLayersControlOptions ###################
# Default options
opts <- groupedLayersControlOptions()
expect_true(opts$groupCheckboxes)
expect_true(opts$groupsCollapsable)
expect_true(opts$collapsed)
expect_true(opts$autoZIndex)

# Custom options
opts <- groupedLayersControlOptions(
exclusiveGroups = "Layergroup_1",
groupCheckboxes = FALSE,
groupsCollapsable = FALSE,
groupsExpandedClass = "custom-expanded-class",
groupsCollapsedClass = "custom-collapsed-class",
sortLayers = TRUE,
sortGroups = TRUE,
sortBaseLayers = TRUE,
collapsed = FALSE,
autoZIndex = FALSE
)
expect_identical(opts$exclusiveGroups, "Layergroup_1")
expect_false(opts$groupCheckboxes)
expect_false(opts$groupsCollapsable)
expect_identical(opts$groupsExpandedClass, "custom-expanded-class")
expect_identical(opts$groupsCollapsedClass, "custom-collapsed-class")
expect_true(opts$sortLayers)
expect_true(opts$sortGroups)
expect_true(opts$sortBaseLayers)
expect_false(opts$collapsed)
expect_false(opts$autoZIndex)

## Test addGroupedOverlay ###################
ts <- leaflet() %>%
addGroupedOverlay(group = "Markers1", name = "Markers1 Layer", groupname = "MarkersGroup")
expect_s3_class(ts, "leaflet")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "addGroupedOverlay")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[2]], "Markers1 Layer")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[3]], "MarkersGroup")

## Test addGroupedBaseLayer ###################
ts <- leaflet() %>%
addGroupedBaseLayer(group = "Markers1", name = "Markers1 Base Layer")
expect_s3_class(ts, "leaflet")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "addGroupedBaseLayer")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[2]], "Markers1 Base Layer")

## Test removeGroupedOverlay ###################
ts <- leaflet() %>%
removeGroupedOverlay(group = "Markers1")
expect_s3_class(ts, "leaflet")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "removeGroupedOverlay")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$args[[1]], "Markers1")

## Test removeGroupedLayersControl ###################
ts <- leaflet() %>%
removeGroupedLayersControl()
expect_s3_class(ts, "leaflet")
expect_identical(ts$x$calls[[length(ts$x$calls)]]$method, "removeGroupedLayersControl")
})
124 changes: 124 additions & 0 deletions tests/testthat/test-map-controls.R
Original file line number Diff line number Diff line change
Expand Up @@ -633,6 +633,130 @@ test_that("map-control-plugins", {
)
))

## Test draw toolbarOptions
opts <- toolbarOptions()
expect_true(is.list(opts))
expect_equal(opts$actions$title, "Cancel drawing")
expect_equal(opts$actions$text, "Cancel")
expect_equal(opts$finish$title, "Finish drawing")
expect_equal(opts$finish$text, "Finish")
expect_equal(opts$undo$title, "Delete last point drawn")
expect_equal(opts$undo$text, "Delete last point")
expect_equal(opts$buttons$polyline, "Draw a polyline")
expect_equal(opts$buttons$polygon, "Draw a polygon")
expect_equal(opts$buttons$rectangle, "Draw a rectangle")
expect_equal(opts$buttons$circle, "Draw a circle")
expect_equal(opts$buttons$marker, "Draw a marker")
expect_equal(opts$buttons$circlemarker, "Draw a circlemarker")

# Custom options
custom_opts <- toolbarOptions(
actions = list(title = "Stop", text = "Stop Drawing"),
finish = list(title = "Complete", text = "Complete Drawing"),
undo = list(title = "Undo", text = "Undo Last"),
buttons = list(
polyline = "Custom Polyline",
polygon = "Custom Polygon",
rectangle = "Custom Rectangle",
circle = "Custom Circle",
marker = "Custom Marker",
circlemarker = "Custom Circlemarker"
)
)
expect_true(is.list(custom_opts))
expect_equal(custom_opts$actions$title, "Stop")
expect_equal(custom_opts$actions$text, "Stop Drawing")
expect_equal(custom_opts$finish$title, "Complete")
expect_equal(custom_opts$finish$text, "Complete Drawing")
expect_equal(custom_opts$undo$title, "Undo")
expect_equal(custom_opts$undo$text, "Undo Last")
expect_equal(custom_opts$buttons$polyline, "Custom Polyline")
expect_equal(custom_opts$buttons$polygon, "Custom Polygon")
expect_equal(custom_opts$buttons$rectangle, "Custom Rectangle")
expect_equal(custom_opts$buttons$circle, "Custom Circle")
expect_equal(custom_opts$buttons$marker, "Custom Marker")
expect_equal(custom_opts$buttons$circlemarker, "Custom Circlemarker")

# edithandlersOptions
edit_opts <- edithandlersOptions()
expect_true(is.list(edit_opts))
expect_equal(edit_opts$edit$tooltip$text, "Drag handles or markers to edit features.")
expect_equal(edit_opts$edit$tooltip$subtext, "Click cancel to undo changes.")
expect_equal(edit_opts$remove$tooltip$text, "Click on a feature to remove.")

# Custom options
custom_edit_opts <- edithandlersOptions(
edit = list(
tooltipText = "Edit features by dragging.",
tooltipSubtext = "Undo changes by clicking cancel."
),
remove = list(
tooltipText = "Select a feature to delete."
)
)
expect_true(is.list(custom_edit_opts))
expect_equal(custom_edit_opts$edit$tooltip$text, "Edit features by dragging.")
expect_equal(custom_edit_opts$edit$tooltip$subtext, "Undo changes by clicking cancel.")
expect_equal(custom_edit_opts$remove$tooltip$text, "Select a feature to delete.")


## Test edittoolbarOptions ###################
edit_opts <- edittoolbarOptions()
expect_true(is.list(edit_opts))

# Test actions
expect_equal(edit_opts$actions$save$title, "Save changes")
expect_equal(edit_opts$actions$save$text, "Save")
expect_equal(edit_opts$actions$cancel$title, "Cancel editing, discards all changes")
expect_equal(edit_opts$actions$cancel$text, "Cancel")
expect_equal(edit_opts$actions$clearAll$title, "Clear all layers")
expect_equal(edit_opts$actions$clearAll$text, "Clear All")

# Test buttons
expect_equal(edit_opts$buttons$edit, "Edit layers")
expect_equal(edit_opts$buttons$editDisabled, "No layers to edit")
expect_equal(edit_opts$buttons$remove, "Delete layers")
expect_equal(edit_opts$buttons$removeDisabled, "No layers to delete")

# Custom options
custom_edit_opts <- edittoolbarOptions(
actions = list(
save = list(
title = "Save the current changes",
text = "Apply"
),
cancel = list(
title = "Discard changes",
text = "Undo"
),
clearAll = list(
title = "Remove all layers",
text = "Remove All"
)
),
buttons = list(
edit = "Modify layers",
editDisabled = "No editable layers",
remove = "Erase layers",
removeDisabled = "No removable layers"
)
)

expect_true(is.list(custom_edit_opts))

# Test custom actions
expect_equal(custom_edit_opts$actions$save$title, "Save the current changes")
expect_equal(custom_edit_opts$actions$save$text, "Apply")
expect_equal(custom_edit_opts$actions$cancel$title, "Discard changes")
expect_equal(custom_edit_opts$actions$cancel$text, "Undo")
expect_equal(custom_edit_opts$actions$clearAll$title, "Remove all layers")
expect_equal(custom_edit_opts$actions$clearAll$text, "Remove All")

# Test custom buttons
expect_equal(custom_edit_opts$buttons$edit, "Modify layers")
expect_equal(custom_edit_opts$buttons$editDisabled, "No editable layers")
expect_equal(custom_edit_opts$buttons$remove, "Erase layers")
expect_equal(custom_edit_opts$buttons$removeDisabled, "No removable layers")

## This doesnt throw an error but it doesnt work. Console-errors.. Should we emit a warning?
# drawmark <- drawMarkerOptions(
Expand Down

0 comments on commit d8333df

Please sign in to comment.