Skip to content

Commit

Permalink
correct capacity when two-way roads converted to one-way in each dire…
Browse files Browse the repository at this point in the history
…ction
  • Loading branch information
StevePem committed Jul 4, 2024
1 parent c5acf4d commit 64cadf6
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 7 deletions.
8 changes: 6 additions & 2 deletions functions/combineRedundantEdges.R
Original file line number Diff line number Diff line change
Expand Up @@ -113,12 +113,16 @@ combineRedundantEdges <- function(nodes_current,edges_current,outputCrs){


# Adding the undirected and directed edges, and setting any edges with zero
# lanes to one.
# lanes to one (if one-way) or two (if two)
edges_all <- bind_rows(
edges_undirected_merged,
edges_directed_opposite_merged%>%filter(is_oneway==1)
) %>%
mutate(permlanes=ifelse(permlanes==0,1,permlanes))
mutate(permlanes = case_when(
permlanes == 0 & is_oneway == 1 ~ 1,
permlanes == 0 & is_oneway == 0 ~ 2,
TRUE ~ permlanes
))

# Finding the geometry
edges_geom <- edges_current %>%
Expand Down
8 changes: 6 additions & 2 deletions functions/combineUndirectedAndDirectedEdges.R
Original file line number Diff line number Diff line change
Expand Up @@ -64,10 +64,14 @@ combineUndirectedAndDirectedEdges <- function(nodes_current,edges_current,output
# directed edges need the from id and to id in the correct order
mutate(from_id=ifelse(from_id_directed==-1,from_id,from_id_directed)) %>%
mutate(to_id=ifelse(to_id_directed==-1,to_id,to_id_directed)) %>%
# Setting any edges with zero lanes to one.
mutate(permlanes=ifelse(permlanes==0,1,permlanes)) %>%
# Only road edges can be one way
mutate(is_oneway=ifelse(is_car==0,0,is_oneway)) %>%
# Setting any edges with zero lanes to one (if one-way) or two (if two-way)
mutate(permlanes = case_when(
permlanes == 0 & is_oneway == 1 ~ 1,
permlanes == 0 & is_oneway == 0 ~ 2,
TRUE ~ permlanes
)) %>%
dplyr::select(-current_group,-from_id_directed,-to_id_directed)

# geometry of shortest edges
Expand Down
5 changes: 3 additions & 2 deletions functions/makeEdgesOneway.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,10 @@ makeEdgesOneway <- function(nodes_current, edges_current) {
names.to.change <- c("fromX", "fromY", "toX", "toY")
edges_current <- rename_with(edges_current, tolower, any_of(names.to.change))

# for two-way, divide permlanes by 2, rounded up (as they will be split into 2 * one-way)
# for two-way, divide permlanes and capacity by 2, rounded up (as they will be split into 2 * one-way)
edges_current <- edges_current %>%
mutate(permlanes = ifelse(is_oneway == 0, ceiling(permlanes / 2), permlanes))
mutate(permlanes = ifelse(is_oneway == 0, ceiling(permlanes / 2), permlanes),
capacity = ifelse(is_oneway == 0, ceiling(capacity / 2), capacity))

# select only two-way edges
edges_twoway <- edges_current %>%
Expand Down
4 changes: 4 additions & 0 deletions functions/processOsmTags.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,10 @@ processOsmTags <- function(osm_df,this_defaults_df){
newLanes = ifelse(df$is_oneway[1] == 0, df$permlanes[1] * 2, df$permlanes[1])
df$permlanes[1] = newLanes
}
} else {
# if no tags, then lanes is default number, multiplied by 2 if two-way
newLanes = ifelse(df$is_oneway[1] == 0, df$permlanes[1] * 2, df$permlanes[1])
df$permlanes[1] = newLanes
}
return(df)
}
Expand Down
2 changes: 1 addition & 1 deletion functions/restructureData.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ restructureData <- function(networkList, highway_lookup,
mutate(freespeed=defaults_df$freespeed[16]) %>%
mutate(laneCapacity=defaults_df$laneCapacity[16]) %>%
mutate(is_car=0) %>%
mutate(permlanes=1) %>% # bikepaths are assumed sinlge lane
mutate(permlanes=2) %>% # bikepaths are assumed one lane in each direction
mutate(is_oneway=0) %>% # bikepaths are assumed bi-directional
dplyr::select(-uid)
# merging changed bikepaths back with rest of the links
Expand Down

0 comments on commit 64cadf6

Please sign in to comment.