diff --git a/.Rbuildignore b/.Rbuildignore index 43b4625..a887eb0 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -11,3 +11,4 @@ ^ignore$ ^austraits$ ^codecov\.yml$ +^inst/cheatsheet$ diff --git a/.github/workflows/test-coverage.yml b/.github/workflows/test-coverage.yml index 52152ec..b2889c5 100644 --- a/.github/workflows/test-coverage.yml +++ b/.github/workflows/test-coverage.yml @@ -3,7 +3,6 @@ on: branches: - master - develop - - upgrade pull_request: branches: - master diff --git a/DESCRIPTION b/DESCRIPTION index 18ce84e..c96475b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,12 +1,17 @@ Package: austraits Title: Helpful functions to access, summarise and wrangle austraits data -Version: 2.2.3 +Version: 3.0.0.9000 Authors@R: c(person(given = "Daniel", family = "Falster", role = "aut", email = "daniel.falster@unsw.edu.au", comment = c(ORCID = "0000-0002-9814-092X")), + person(given = "Elizabeth", + family = "Wenk", + role = "ctb", + email = "e.wenk@unsw.edu.au", + comment = c(ORCID = "0000-0001-5640-5910")), person(given = "Fonti", family = "Kar", role = c("aut", "cre"), @@ -22,7 +27,7 @@ Encoding: UTF-8 Language: en LazyData: true Roxygen: list(markdown = TRUE) -RoxygenNote: 7.2.3 +RoxygenNote: 7.3.2 Depends: R (>= 4.0.0), RefManageR @@ -32,19 +37,21 @@ Imports: rlang, purrr, tidyselect, - assertthat, stringr, stats, jsonlite, utils, magrittr, janitor, - lifecycle + lifecycle, + tibble, + cli Suggests: ggplot2, ggpointdensity, ggbeeswarm (>= 0.7.1), gridExtra, + readr, scales, forcats, viridis, diff --git a/NAMESPACE b/NAMESPACE index eea0d50..d132b9e 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,41 +1,41 @@ # Generated by roxygen2: do not edit by hand -S3method(print,austraits) +S3method(print,traits.build) export("%>%") export(as_wide_table) +export(bind_databases) export(bind_trait_values) +export(convert_df_to_list) +export(convert_list_to_df1) +export(convert_list_to_df2) +export(extract_data) export(extract_dataset) export(extract_taxa) export(extract_trait) +export(flatten_database) export(get_version_latest) export(get_versions) -export(join_all) -export(join_contexts) -export(join_locations) +export(join_context_properties) +export(join_contributors) +export(join_location_coordinates) +export(join_location_properties) export(join_methods) -export(join_sites) -export(join_taxonomy) +export(join_taxa) +export(join_taxonomic_updates) export(load_austraits) +export(lookup_context_property) +export(lookup_location_property) export(lookup_trait) export(plot_locations) export(plot_site_locations) export(plot_trait_distribution_beeswarm) export(separate_trait_values) -export(summarise_austraits) -export(summarise_trait_means) +export(summarise_database) export(trait_pivot_longer) export(trait_pivot_wider) import(RefManageR) -importFrom(dplyr,arrange) -importFrom(dplyr,filter) -importFrom(dplyr,group_by) -importFrom(dplyr,select) -importFrom(dplyr,summarise) importFrom(lifecycle,deprecated) importFrom(magrittr,"%>%") +importFrom(rlang,.data) importFrom(stats,family) -importFrom(stringr,str_detect) -importFrom(tidyr,pivot_longer) -importFrom(tidyr,pivot_wider) -importFrom(tidyselect,all_of) importFrom(utils,methods) diff --git a/NEWS.md b/NEWS.md index d672128..2c23014 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,2 +1,17 @@ -# austraits 2.2.1 +# austraits 3.0.0.9000 - Updated dependencies, placing graphics related packages in Suggests +- Added internal function to check the compatibility of databases +- Added internal function notify users that some database versions will not be supported +- The following functions will no longer support AusTraits version < 5.0.0: + - `extract_*` + - `trait_pivot_wider` + - `join_*` + - `plot_site/locations` + - `plot_trait_beeswarm` + - `as_wide_table` +- `trait_pivot_longer` is deprecated +- `summarise_trait_means` will trigger warning due to uninformed calculations +- Added new function `extract_data` +- Added new function `bind_databases` +- Added new function `flatten_databases` +- Updated print function `print.traits.build` \ No newline at end of file diff --git a/R/as_wide_table.R b/R/as_wide_table.R index 2c097a0..eec13b9 100644 --- a/R/as_wide_table.R +++ b/R/as_wide_table.R @@ -1,6 +1,6 @@ -#' Create a single wide table from the AusTraits data object +#' Create a single wide table from a traits.build data object #' -#' @param austraits austraits data object +#' @param database traits.build database (list object) #' #' @return A single wide table with collapsed contexts and locations text and with #' some cols renamed for alignment with other resources @@ -8,27 +8,19 @@ #' #' @examples #' \dontrun{ -#' data <- austraits -#' data %>% as_wide_table() +#' austraits %>% as_wide_table() #' } #' @importFrom stats family #' @importFrom utils methods -as_wide_table <- function(austraits){ - # Switch for different versions - version <- what_version(austraits) +as_wide_table <- function(database){ + # Check compatability + status <- check_compatibility(database) - switch (version, - "5-series" = as_wide_table3(austraits), - "4-series" = as_wide_table2(austraits), - "3-series-earlier" = as_wide_table1(austraits) - ) -} - -#' Turning entire AusTraits object into wide table v5 -#' @noRd -#' @keywords internal -as_wide_table3 <- function(austraits){ + # If compatible + if(!status){ + function_not_supported(database) + } # Function to collapse columns in locations and contexts into single column process_table3 <- function(data) { @@ -40,39 +32,39 @@ as_wide_table3 <- function(austraits){ } ################################################################################ - # Define and adapt each table in the list of austraits to prepare for the wide table format + # Define and adapt each table in the list of a traits.build database to prepare for the wide table format # The contexts table needs the contexts collapsed to one context name per site - austraits %>% - join_contexts(collapse_context = TRUE) -> austraits + database %>% + join_contexts_old(collapse_context = TRUE) -> database # Getting rid of the columns that will soon be deleted in the next austraits release and renaming the description column - austraits$methods <- - austraits$methods %>% + database$methods <- + database$methods %>% dplyr::rename(dataset_description = "description") %>% dplyr::distinct() # collapse into one column - austraits$locations <- - austraits$locations %>% + database$locations <- + database$locations %>% dplyr::filter(value!="unknown") %>% dplyr::rename("property" = "location_property") %>% split(., .$dataset_id) %>% purrr::map_dfr(process_table3) # rename taxonomic_dataset field to reflect the APC/APNI name matching process better - austraits$taxa <- - austraits$taxa %>% + database$taxa <- + database$taxa %>% dplyr::distinct() - austraits_wide <- - austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "location_id"), austraits$locations) %>% - dplyr::left_join(by=c("dataset_id", "method_id", "trait_name"), austraits$methods) %>% - dplyr::left_join(by=c("taxon_name"), austraits$taxa) + database_wide <- + database$traits %>% + dplyr::left_join(by=c("dataset_id", "location_id"), database$locations) %>% + dplyr::left_join(by=c("dataset_id", "method_id", "trait_name"), database$methods) %>% + dplyr::left_join(by=c("taxon_name"), database$taxa) # reorder the names to be more intuitive - austraits_wide %>% dplyr::select( + database_wide %>% dplyr::select( # The most useful (if you are filtering for just one taxon_name) "dataset_id", "observation_id", "trait_name", "taxon_name", "value", "unit", @@ -99,208 +91,76 @@ as_wide_table3 <- function(austraits){ "taxon_rank", "genus", "family" ) - austraits_wide + database_wide } -#' Turning entire AusTraits object into wide table v4 -#' @noRd +#' Collapse columns into text string #' @keywords internal -as_wide_table2 <- function(austraits){ - - # Function to collapse columns in locations and contexts into single column - process_table2 <- function(data) { - data %>% - tidyr::pivot_wider(names_from = "property", values_from = "value") %>% - tidyr::nest(data=-dplyr::any_of(c("dataset_id", "location_id", "latitude (deg)", "longitude (deg)"))) %>% - dplyr::mutate(location = purrr::map_chr(data, collapse_cols)) %>% - dplyr::select(-data) - } - - ################################################################################ - # Define and adapt each table in the list of austraits to prepare for the wide table format - - # The contexts table needs the contexts collapsed to one context name per site - austraits %>% - join_contexts(collapse_context = TRUE) -> austraits - - # Getting rid of the columns that will soon be deleted in the next austraits release and renaming the description column - austraits$methods <- - austraits$methods %>% - dplyr::rename(dataset_description = "description") %>% - dplyr::distinct() - - # collapse into one column - austraits$locations <- - austraits$locations %>% - dplyr::filter(value!="unknown") %>% - dplyr::rename(property = "location_property") %>% - split(., .$dataset_id) %>% - purrr::map_dfr(process_table2) - - # rename taxonomic_dataset field to reflect the APC/APNI name matching process better - austraits$taxa <- - austraits$taxa %>% - dplyr::distinct() - - austraits_wide <- - austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "location_id"), austraits$locations) %>% - dplyr::left_join(by=c("dataset_id", "trait_name"), austraits$methods) %>% - dplyr::left_join(by=c("taxon_name"), austraits$taxa) +#' @noRd +collapse_cols <- function(data) { - # reorder the names to be more intuitive - austraits_wide %>% dplyr::select(dplyr::any_of(c( - - # The most useful (if you are filtering for just one taxon_name) - "dataset_id", "observation_id", "trait_name", "taxon_name", "value", "unit", - "entity_type", "population_id", "individual_id", - "value_type", "basis_of_value", - "replicates", - # tissue, trait_category, # Add after new zenodo release - - # More stuff you can filter on - "collection_date", "basis_of_record", "life_stage", "sampling_strategy", - "treatment_id", "temporal_id", - - #stuff relating to locations - "latitude (deg)", "longitude (deg)", "location", "plot_id", - - #stuff relating to contexts and methods - "context", "methods", "original_name", - - #the citations - "dataset_description", "source_primary_citation", "source_secondary_citation", - - #the taxa details - "taxonomic_status", "taxon_distribution", - "taxon_rank", "genus", "family" - - ) - ) - ) + if(ncol(data) ==0) return(NA_character_) - austraits_wide + data %>% purrr::imap_dfr(~ sprintf("%s='%s'",.y,.x)) %>% + tidyr::unite("text", sep="; ") %>% dplyr::pull(text) } -#' Turning entire AusTraits object into wide table <=3.0.2 +#' Old join contexts function that collapses contexts into a single column and doesn't specify categories of context properties. +#' @keywords internal #' @noRd -#' @keywords internal -as_wide_table1 <- function(austraits){ - - - ################################################################################ - # TODO: this updated with next zenodo release - # Load the trait classification doc - classifies the tissue type and type of trait based on the trait_name data field - # Exclude this for now -- will be added to definitions file in future release - # trait_class = read.csv("data-raw/Trait_classifications_v3.csv") - # trait_class[is.na(trait_class)] = "" - # trait_class <- trait_class %>% as_tibble() - # - # we only need two extra columns from the trait class table - collapsing two category and other_tags cols and renaming them for clarity - # x2 <- - # trait_class %>% dplyr::mutate( - # trait_category = str_c(category, "; ", other_tags) %>% gsub("; $", "", .) - # ) %>% - # dplyr::select(trait_name, tissue, trait_category) - # - # Function to collapse columns in sites and contexts into single column - process_table <- function(data) { - - data %>% - tidyr::pivot_wider(names_from = "property", values_from = "value") %>% - tidyr::nest(data=-dplyr::any_of(c("dataset_id", "site_name", "context_name", "latitude (deg)", "longitude (deg)"))) %>% - dplyr::mutate(site = purrr::map_chr(data, collapse_cols)) %>% - dplyr::select(-data) - } - - ################################################################################ - # Define and adapt each table in the list of austraits to prepare for the wide table format - - # the trait table needs little prep. Rename the value columns as value - austraits$traits <- - austraits$traits %>% - dplyr::rename(trait_value = "value") - - # The contexts table needs the contexts collapsed to one context name per site - austraits$contexts <- - austraits$contexts %>% - dplyr::rename(property = "context_property") %>% - split(austraits$contexts$dataset_id) %>% - purrr::map_dfr(process_table) %>% - dplyr::rename(context = "site") - - # Getting rid of the columns that will soon be deleted in the next austraits release and renaming the description column - austraits$methods <- - austraits$methods %>% - # ----------- - # TODO: this section can be removed for next release - # Some studies have multiple records per traits. This breaks things when joining - # For now select first - dplyr::group_by(dataset_id, trait_name) %>% - dplyr::slice(1) %>% - dplyr:: ungroup() %>% - #------------ - dplyr::select(-c("year_collected_start", "year_collected_end")) %>% - dplyr::rename(dataset_description = "description") - - # collapse into one column - austraits$sites <- - austraits$sites %>% - dplyr::filter(value!="unknown") %>% - # next line is a fix -- one dataset in 3.0.2 has value "site_name" - dplyr::mutate(site_property = gsub("site_name", "name", site_property)) %>% - dplyr::rename(property = "site_property") %>% - split(., .$dataset_id) %>% - purrr::map_dfr(process_table) +join_contexts_old <- function(austraits, collapse_context = FALSE){ + # Check compatability + status <- check_compatibility(austraits) + + # If compatible + if(!status){ + function_not_supported(austraits) + } + + traits2 <- split(austraits$traits, austraits$traits$dataset_id) + contexts2 <- split(austraits$contexts, austraits$contexts$dataset_id) - # rename source data field to reflect the APC/APNI name matching process better - austraits$taxa <- - austraits$taxa %>% - dplyr::rename(taxonNameValidation = "source") + traits_vars <- names(austraits$traits) + + problem_studies <- c("Hall_1981") + + for(id in names(traits2)) { - austraits_wide <- - austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "context_name"), austraits$contexts) %>% - dplyr::left_join(by=c("dataset_id", "site_name"), austraits$sites) %>% - dplyr::left_join(by=c("dataset_id", "trait_name"), austraits$methods) %>% - dplyr::left_join(by=c("taxon_name"), austraits$taxa) %>% + if(!is.null(contexts2[[id]][1]) & ! (id %in% problem_studies)) { - # reorder the names to be more intuitive - dplyr::select( - - # The most useful (if you are filtering for just one taxon_name) - "dataset_id", "observation_id", "trait_name", "taxon_name", "trait_value", "unit", - "value_type", "replicates", - # tissue, trait_category, # Add after new zenodo release - - # More stuff you can filter on - "date", "collection_type", "sample_age_class", "sampling_strategy", - - #stuff relating to sites - "latitude (deg)", "longitude (deg)", "site_name", "site", - - #stuff relating to contexts and methods - "context_name", "context", "methods", "original_name", - - #the citations - "dataset_description", "source_primary_citation", "source_secondary_citation", + context_ids <- + unique(contexts2[[id]]$link_id) + + for(v in context_ids[!is.na(context_ids)]) { + + context_sub <- + contexts2[[id]] %>% + dplyr::select(-dplyr::any_of(c("category", "description"))) %>% + dplyr::filter(link_id == v) %>% + tidyr::separate_rows(link_vals) %>% + tidyr::pivot_wider(values_from = value, names_from = context_property) %>% + tidyr::pivot_wider(names_from = link_id, values_from = link_vals) + + traits2[[id]] <- + dplyr::left_join(by = c("dataset_id", v), + traits2[[id]], + context_sub + ) + } - #the taxa details - "taxonomicStatus", "taxonDistribution", - "taxonRank", "genus", "family", "acceptedNameUsageID", - "scientificNameAuthorship", "ccAttributionIRI" - ) - - austraits_wide -} + if(collapse_context == TRUE){ + context_text <- + traits2[[id]] %>% + dplyr::select(-dplyr::any_of(traits_vars)) %>% collapse_cols() -#' Collapse columns into text string -#' @keywords internal -#' @noRd -collapse_cols <- function(data) { - - if(ncol(data) ==0) return(NA_character_) - - data %>% purrr::imap_dfr(~ sprintf("%s='%s'",.y,.x)) %>% - tidyr::unite("text", sep="; ") %>% dplyr::pull(text) + traits2[[id]] <- traits2[[id]] %>% + dplyr::mutate(context = context_text) %>% + dplyr::select(dplyr::any_of(traits_vars), context) + } + } + } + + austraits$traits <- traits2 %>% dplyr::bind_rows() + + austraits } \ No newline at end of file diff --git a/R/austraits-package.R b/R/austraits-package.R index 48ded33..f81f19e 100644 --- a/R/austraits-package.R +++ b/R/austraits-package.R @@ -6,7 +6,7 @@ if(getRversion() >= "2.15.1") utils::globalVariables(c(".", "dplyr::n()")) .onAttach <- function(libname, pkgname) { - packageStartupMessage("Thanks for showing interest in `austraits`! Please consider citing this package - citation('austraits')") + cli::cli_inform("Thanks for showing interest in `austraits`! Please consider citing this package - citation('austraits')", class = "packageStartupMessage") } #' @keywords internal @@ -17,44 +17,60 @@ if(getRversion() >= "2.15.1") utils::globalVariables(c(".", "dplyr::n()")) ## usethis namespace: end NULL -utils::globalVariables(c("..density..", - ".data", - "Group", - "abort", - "australia", - "colour", - "context", - "context_name", - "context_property", - "dataset_id", - "latitude (deg)", - "link_id", - "link_vals", - "location_name", - "location_property", - "longitude (deg)", - "method_context_id", - "method_id", - "n", - "n_vals", - "n_value_type", - "observation_id", - "original_name", - "percent", - "percent_total", - "repeat_measurements_id", - "replicates", - "shapes", - "site_name", - "site_property", - "source_id", - "taxon_name", - "text", - "trait_name", - "value", - "value_type", - "x", - "y", - "publication_date", - "doi") +utils::globalVariables(c( + "aus_traits", + "..density..", + "description", + ".data", + "doi", + "given_name", + "Group", + "abort", + "australia", + "basis_of_value", + "category", + "colour", + "context", + "context_name", + "context_property", + "contributor", + "data", + "dataset_id", + "data_contributors", + "identifier", + "last_name", + "latitude (deg)", + "link_id", + "link_vals", + "location_id", + "location_name", + "location_property", + "location_properties", + "longitude (deg)", + "method_context_id", + "method_id", + "n", + "name", + "n_vals", + "n_value_type", + "observation_id", + "original_name", + "percent", + "percent_total", + "publication_date", + "repeat_measurements_id", + "relation_type", + "replicates", + "shapes", + "site_name", + "site_property", + "source_id", + "taxon_name", + "text", + "trait_name", + "value", + "value_type", + "x", + "y" +) ) diff --git a/R/bind_databases.R b/R/bind_databases.R new file mode 100644 index 0000000..0053e06 --- /dev/null +++ b/R/bind_databases.R @@ -0,0 +1,70 @@ +#' Bind multiple traits.build data objects into a single data object +#' +#' `bind_databases` binds all the listed studies into a single traits.build +#' database object as a large list. +#' +#' @param ... Arguments passed to other functions +#' @param database_1 List of traits.build databases to bind together +#' +#' @return Compiled database as a single large list +#' @importFrom rlang .data +#' @export +bind_databases <- function(..., databases = list(...)) { + + combine <- function(name, databases) { + dplyr::bind_rows(lapply(databases, "[[", name)) %>% dplyr::distinct() + } + + # Bind sources and remove duplicates + sources <- databases %>% lapply("[[", "sources") + keys <- sources %>% lapply(names) %>% unlist() %>% unique() %>% sort() + sources <- sources %>% purrr::reduce(c) + sources <- sources[keys] + + definitions <- databases %>% lapply("[[", "definitions") %>% purrr::reduce(c) + definitions <- definitions[!duplicated(names(definitions))] + definitions <- definitions[sort(names(definitions))] + + # Drop null datasets + databases[sapply(databases, is.null)] <- NULL + + # Taxonomy + + taxonomic_updates <- + combine("taxonomic_updates", databases) %>% + dplyr::group_by(.data$original_name, .data$aligned_name, .data$taxon_name, .data$taxonomic_resolution) %>% + #dplyr::mutate(dataset_id = paste(.data$dataset_id, collapse = " ")) %>% + dplyr::ungroup() %>% + dplyr::distinct() %>% + dplyr::arrange(.data$original_name, .data$aligned_name, .data$taxon_name, .data$taxonomic_resolution) + + # Metadata + contributors <- combine("contributors", databases) + metadata <- databases[[1]][["metadata"]] + + metadata[["contributors"]] <- + contributors %>% + dplyr::select(-dplyr::any_of(c("dataset_id", "additional_role"))) %>% + dplyr::distinct() %>% + dplyr::arrange(.data$last_name, .data$given_name) %>% + convert_df_to_list() + + ret <- list(traits = combine("traits", databases) %>% dplyr::arrange(.data$dataset_id, .data$observation_id, .data$trait_name), + locations = combine("locations", databases) %>% dplyr::arrange(.data$dataset_id, .data$location_id), + contexts = combine("contexts", databases) %>% dplyr::arrange(.data$dataset_id, .data$category), + methods = combine("methods", databases) %>% dplyr::arrange(.data$dataset_id, .data$trait_name), + excluded_data = combine("excluded_data", databases) %>% dplyr::arrange(.data$dataset_id, .data$observation_id, .data$trait_name), + taxonomic_updates = taxonomic_updates, + taxa = combine("taxa", databases) %>% dplyr::distinct() %>% dplyr::arrange(.data$taxon_name), + contributors = contributors, + sources = sources, + definitions = definitions, + schema = databases[[1]][["schema"]], + metadata = metadata, + build_info = list(session_info = utils::sessionInfo()) + ) + + class(ret) <- c("list", "traits.build") + + ret +} diff --git a/R/bind_trait_values.R b/R/bind_trait_values.R index 147b23a..7b17005 100644 --- a/R/bind_trait_values.R +++ b/R/bind_trait_values.R @@ -3,13 +3,13 @@ #' @description This function condenses data for studies that have multiple observations for a given trait into a single row. #' This function concatenates multiple values into a single cell #' @usage bind_trait_values(trait_data) -#' @param trait_data The trait data frame generated from austraits - see example +#' @param trait_data the traits table in a traits.build database -- see example #' @return tibble that is condensed down where multiple observations in value, value_type and replicates are collapsed down and separated by '--' #' #' @examples #' \dontrun{ #' traits <- austraits$traits %>% -#' dplyr::filter(dataset_id == "Falster_2005_1") +#' dplyr::filter(dataset_id == "ABRS_1981") #' traits #' traits_bind <- bind_trait_values(traits) #' } @@ -28,6 +28,7 @@ bind_trait_values <- function(trait_data) { .data %>% dplyr::mutate(value = bind_x(.data$value), value_type = bind_x(value_type), + basis_of_value = bind_x(basis_of_value), replicates = bind_x(replicates)) %>% dplyr::filter(dplyr::row_number()==1) ) @@ -36,8 +37,8 @@ bind_trait_values <- function(trait_data) { } trait_data %>% - dplyr::group_by(observation_id, trait_name) %>% + dplyr::group_by(dataset_id, observation_id, trait_name, method_id, method_context_id, repeat_measurements_id) %>% bind_values_worker() %>% dplyr::ungroup() %>% - dplyr::arrange(observation_id, trait_name, value_type) + dplyr::arrange(dataset_id, observation_id, trait_name, value_type, method_id, method_context_id, repeat_measurements_id) } diff --git a/R/check_compatibility.R b/R/check_compatibility.R new file mode 100644 index 0000000..8c0cde3 --- /dev/null +++ b/R/check_compatibility.R @@ -0,0 +1,81 @@ +#' @title Check compatibility of traits.build object +#' @description Function to check whether the data object has been compiled by the traits.build workflow and +#' therefore has a data structure that is appropriate for use with austraits functions. +#' @param database traits.build database (list object) +#' @param single_table_allowed logical for when the input might be a single table instead of a complete database; defaults to FALSE +#' +#' @return logical (T/F) output and messaging for uncompatible versions +#' +#' @examples +#' \dontrun{ +#' check_compatibility(database) +#' } +#' @author Elizabeth Wenk - e.wenk@unsw.edu.au + +check_compatibility <- function(database, single_table_allowed = FALSE) { + + if (!is.null(dim(database)) & single_table_allowed == TRUE) { + + compatible <- TRUE + + } else { + + if (is.null(database$metadata)) { + + compatible <- FALSE + + # message("You are working with AusTraits version 3.0 or earlier. \nThis database structure is unsupported by the current version of this package. \nPlease see https://github.com/traitecoevo/austraits for details on installing old versions of the package.") + + } else { + + compiled_by_traits.build <- + get_compiled_by_traits.build(database) + + if(is.null(compiled_by_traits.build) | nrow(compiled_by_traits.build) > 0) { + compatible <- TRUE + } else{ + compatible <- FALSE + + # message("You are working with AusTraits version 4, which is unsupported by the current version of this package. \nPlease see https://github.com/traitecoevo/austraits for details on installing old versions of the package.") + } + + } + + } + + invisible(compatible) + +} + + + + +#' Check compatibility of traits table +#' +#' @param trait_data the traits table in a traits.build database +#' +#' @return logical, TRUE indicating version traits table came from traits.build version > 1.0 + +check_traits_compatibility <- function(trait_data){ + # Check compatibility using column + if(any(names(trait_data) %in% c("treatment_context_id", "repeat_measurements_id"))){ + compatible <- TRUE + } else + compatible <- FALSE + + invisible(compatible) +} + + +#' Retrieve compiled by information from metadata table +#' +#' @param database traits.build database +#' +#' @return logical, TRUE indicating version traits table came from traits.build version > 1.0 + +get_compiled_by_traits.build <- function(database){ + database$metadata$related_identifiers %>% + convert_list_to_df2() %>% + dplyr::filter(relation_type == "isCompiledBy") %>% + dplyr::filter(stringr::str_detect(identifier, "github.com/traitecoevo/traits.build")) +} \ No newline at end of file diff --git a/R/clean_NA.R b/R/clean_NA.R deleted file mode 100644 index 6d181da..0000000 --- a/R/clean_NA.R +++ /dev/null @@ -1,18 +0,0 @@ -#' @title NA hygiene -#' -#' @description Helper function to convert character strings of NA into true NA -#' @usage clean_NA(x) -#' @param data The trait data frame generated from austraits - see example -#' @param definitions The austraits definitions data frame -#' @return vector where strings of NA are treated as true NA -#' @examples -#' \dontrun{ -#' clean_NA(c("NA", 1, 2, 3))) %>% is.na() -#' } -#' @author Daniel Falster - daniel.falster@unsw.edu.au - -#' @noRd - -clean_NA <- function(x) { - ifelse(x == "NA", NA_character_, x) -} diff --git a/R/extract_data.R b/R/extract_data.R new file mode 100644 index 0000000..c1e8007 --- /dev/null +++ b/R/extract_data.R @@ -0,0 +1,246 @@ +#' Extract data from traits.build database +#' +#' @description Function to extract data from a traits.build database based on +#' any value(s) from any column in the traits, locations, contexts, methods, +#' taxa, taxonomic_updates, and contributors tables. +#' The output a traits.build formatted database with all tables subset +#' based on the specified table, column (variable) and column value. +#' +#' @param database traits.build database (list object) +#' @param table Table within a traits.build database +#' @param col Column name within the specified table. +#' @param col_value Value (of column, from with a table) that is used to subset database. This can be a single value or a vector. It includes partial string matches. +#' +#' @return subset traits.build database +#' @export +#' +#' @examples +#' \dontrun{ +#' extract_data(database = traits.build_database, table = "traits", +#' col = "trait_name", col_value = "leaf_area") +#' } +extract_data <- function(database, table = NA, col, col_value) { + + # Check compatability + status <- check_compatibility(database, single_table_allowed = TRUE) + + # If compatible + if(!status){ + function_not_supported(database) + } + + # If just the traits table is read in + if (tibble::is_tibble(database)) { + + indicies_tmp <- purrr::map(col_value, ~{ + stringr::str_which(database[[col]], + pattern = stringr::regex(.x, ignore_case = TRUE)) + }) + + found_indicies <- purrr::reduce(indicies_tmp, union) + + # Trim traits, based on the columns identified + ret <- database %>% + dplyr::slice(found_indicies) + + # If a full traits.build database is read in + } else { + + database$contexts <- database$contexts %>% tidyr::separate_longer_delim(link_vals, delim = ", ") + + database$contexts_tmp <- split(database$contexts, database$contexts$link_id) + + empty_tibble <- dplyr::tibble( + dataset_id = character(), + context_property = character(), + category = character(), + value = character(), + description = character(), + link_id = character(), + link_vals = character() + ) + + # Create an empty database list + ret <- list( + locations = dplyr::tibble(), + entity_context_id = dplyr::tibble(), + method_context_id = dplyr::tibble(), + temporal_context_id = dplyr::tibble(), + plot_context_id = dplyr::tibble(), + treatment_context_id = dplyr::tibble(), + methods = dplyr::tibble(), + taxa = dplyr::tibble(), + taxonomic_updates = dplyr::tibble(), + contributors = dplyr::tibble(), + traits = dplyr::tibble(), + excluded_data = dplyr::tibble(), + contexts = dplyr::tibble() + ) + + ret_tmp <- ret[1:10] + + # Cookie cutters + cookie_cutters <- list( + locations_cc = c("dataset_id", "location_id"), + entity_contexts_cc = c("dataset_id", "entity_context_id"), + method_contexts_cc = c("dataset_id", "method_context_id"), + temporal_contexts_cc = c("dataset_id", "temporal_context_id"), + plot_contexts_cc = c("dataset_id", "plot_context_id"), + treatment_contexts_cc = c("dataset_id", "treatment_context_id"), + methods_cc = c("dataset_id", "trait_name", "method_id"), + taxa_cc = c("taxon_name"), + taxonomic_updates_cc = c("dataset_id", "taxon_name", "original_name"), + contributors_cc = c("dataset_id") + ) + + # Create table of various look-up values to be used below + + # Create additional vectors for table + tables_to_cut <- c("locations", "entity_context_id", "method_context_id", "temporal_context_id", + "plot_context_id", "treatment_context_id", + "methods", "taxa", "taxonomic_updates", "contributors") + + tables_complete_path <- c("database$locations", "database$entity_context_id", + "database$method_context_id", "database$temporal_context_id", + "database$plot_context_id", "database$treatment_context_id", + "database$methods", "database$taxa", "database$taxonomic_updates", "database$contributors") + + # Create table + tables <- dplyr::tibble( + cookie_cutters = names(cookie_cutters), + tables_to_cut = tables_to_cut, + tables_complete_path = tables_complete_path + ) + + # For any context property categories that do not exist, create empty tibbles. + for (v in c("entity_context_id", "method_context_id", "temporal_context_id", "plot_context_id", "treatment_context_id")) { + if (is.null(database$contexts_tmp[[v]])) { + database$contexts_tmp[[v]] <- empty_tibble + } + } + + # Rename the generic `link_vals` to the specific context category they represent and + # move the tables from database_tmp to the main database list. + + for (z in c("entity_context_id", "method_context_id", "temporal_context_id", + "plot_context_id", "treatment_context_id")) { + database[[z]] <- database$contexts_tmp[[z]] %>% + dplyr::rename(!!z := link_vals) + } + + # If the context table is queried need to convert the word "contexts" into a vector that indicates which of the 5 context categories have matches + if (table == "contexts") { + + table_tmp <- database$contexts %>% + dplyr::filter(stringr::str_detect(database$contexts[[col]], col_value)) %>% + dplyr::distinct(link_id) + + table <- as.vector(table_tmp[[1]]) + + if (length(table) == 0) { + table <- as.vector("treatment_context_id") + } + + } + + for (i in seq_along(1:length(table))) { + + tables_tmp <- tables + + # chose columns to select, ensuring "value" isn't among the columns, since it has a different meaning for each table + columns_to_select <- intersect(setdiff(names(database$traits), "value"), names(database[[table[[i]]]])) + + indicies_tmp <- purrr::map(col_value, ~{ + stringr::str_which(database[[table[[i]]]][[col]], + pattern = stringr::regex(.x, ignore_case = TRUE)) + }) + + found_indicies <- purrr::reduce(indicies_tmp, union) + + # Trim traits, based on the columns identified as being common between the traits table and target table + cc_traits <- database[[table[[i]]]] %>% + dplyr::slice(found_indicies) %>% + dplyr::select(tidyselect::all_of(columns_to_select)) %>% + dplyr::distinct() + + # Filtering join + ## It will quite literally cookie cutting the traits table if the columns match what is in cc_traits + ret_tmp[["traits"]] <- database[["traits"]]%>% + dplyr::semi_join(cc_traits, by = columns_to_select) + + columns_to_select_excluded <- intersect(setdiff(names(database$excluded_data), "value"), names(database[[table[[i]]]])) + + # Use same filtering join to trim excluded data + ret_tmp[["excluded_data"]] <- database[["excluded_data"]] %>% + dplyr::semi_join(cc_traits, by = columns_to_select_excluded) + + + for (j in seq_along(tables_tmp$tables_to_cut)) { + + cut_traits <- ret_tmp[["traits"]] %>% + dplyr::select(cookie_cutters[[j]]) %>% + dplyr::distinct() + + cut_traits <- cut_traits %>% + dplyr::filter(dplyr::if_all(tidyselect::everything(), ~ !is.na(.))) + + cut_table <- eval(parse(text = tables_tmp$tables_complete_path[[j]])) %>% + dplyr::semi_join(cut_traits, by = cookie_cutters[[j]]) %>% + dplyr::rename(link_vals = tidyselect::contains("context_id")) + + ret_tmp[[j]] <- cut_table + + } + + for (v in seq_along(c(tables$tables_to_cut, "traits", "excluded_data"))) { + + ret[[v]] <- ret[[v]] %>% + dplyr::bind_rows(ret_tmp[[v]]) %>% + dplyr::distinct() + + } + + } + + # Rejoin contexts + ret[["contexts"]] <- ret[["entity_context_id"]] %>% + dplyr::bind_rows(ret[["method_context_id"]], + ret[["plot_context_id"]], + ret[["temporal_context_id"]], + ret[["treatment_context_id"]]) %>% + dplyr::select(-dplyr::any_of(c("entity_context_id", "method_context_id", "plot_context_id", "temporal_context_id", "treatment_context_id"))) %>% + dplyr::group_by(dataset_id, category, link_id, value, description) %>% + dplyr::mutate(link_vals = paste0(link_vals, collapse = ", ")) %>% + dplyr::ungroup() %>% + dplyr::distinct() + + ret <- ret[!names(ret) %in% c("entity_context_id", "method_context_id", "plot_context_id", "temporal_context_id", "treatment_context_id")] + + # Trim sources - Are these just dataset_ids... + from_methods_to_sources_cc <- dplyr::union(ret$methods$source_primary_key, # Is this part really needed, aren't these just dataset_ids? + ret$methods$source_secondary_key %>% strsplit("; ") %>% unlist()) %>% + unique() %>% stats::na.omit() %>% as.character() + + ret[["sources"]] <- database[["sources"]][from_methods_to_sources_cc] + + # Join in other metadata tables + ret[["definitions"]] <- database[["definitions"]] + ret[["schema"]] <- database[["schema"]] + ret[["metadata"]] <- database[["metadata"]] + ret[["build_info"]] <- database[["build_info"]] + + # Reorder list to match database + ret <- ret[c("traits", "locations", "contexts", "methods", "excluded_data", "taxonomic_updates", + "taxa","contributors","sources","definitions","schema", "metadata","build_info")] + + # Assign class + attr(data, "class") <- "traits.build" + + } + + ret + +} + + + diff --git a/R/extract_dataset.R b/R/extract_dataset.R index 15b903a..e7bb123 100644 --- a/R/extract_dataset.R +++ b/R/extract_dataset.R @@ -1,102 +1,40 @@ #' @title Extract all data for a particular dataset #' -#' @description Function to subset of all data associated with a particular dataset from austraits -#' @usage extract_dataset(austraits, dataset_id) -#' @param austraits - A large list of tibbles built from austraits -#' @param dataset_id - character string that matches a dataset_id in the data -#' @return A large list of tibbles containing all austraits information for one particular dataset +#' @description Function to subset all data associated with a particular dataset from a traits.build relational database. +#' +#' @usage extract_dataset(database, dataset_id) +#' @param database traits.build database (list object) +#' @param dataset_id character string that matches a `dataset_id` in the database +#' @return List of tibbles containing all traits.build data and metadata for the specified dataset(s). +#' @details +#' `extract_dataset` has been developed to extract data for specific datasets from databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. #' #' @examples #' \dontrun{ -#' extract_dataset(austraits, "Falster_2003") +#' extract_dataset(database, "Falster_2003") #' } #' @author Daniel Falster - daniel.falster@unsw.edu.au #' @export -extract_dataset <- function(austraits, dataset_id) { - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" +extract_dataset <- function(database, dataset_id) { - switch (version, - 'new' = extract_dataset2(austraits, dataset_id), - 'old' = extract_dataset1(austraits, dataset_id), - ) -} + # Check compatability + status <- check_compatibility(database, single_table_allowed = TRUE) -#' @title Extract specific dataset from austraits object for versions <=3.0.2 -#' @rdname extract_dataset -extract_dataset1 <- function(austraits, dataset_id){ - austraits$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - ret <- list() - for(v in c("traits", "sites", "contexts", "methods", "excluded_data", "taxonomic_updates", "contributors")) - ret[[v]] <- austraits[[v]][ austraits[[v]][["dataset_id"]] %in% dataset_id,] - # NB: can't use dplyr::filter in the above as it doesn't behave when the variable name is the same as a column name - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - - ret[["definitions"]] <- austraits[["definitions"]] - ret[["build_info"]] <- austraits[["build_info"]] - - keys <- dplyr::union(ret$methods$source_primary_key, - ret$methods$source_secondary_key %>% strsplit("; ") %>% unlist()) %>% - unique() %>% stats::na.omit() %>% as.character() - - ret[["sources"]] <- austraits$sources[keys] - - ret[["sources"]] <- austraits[["sources"]][keys] - - assertthat::are_equal(sort(names(austraits)), sort(names(ret))) - - ret[names(austraits)] - - # Assign class - attr(ret, "class") <- "austraits" + # If compatible + if(!status){ + function_not_supported(database) + } - ret + extract_data(database, "traits", "dataset_id", col_value = dataset_id) } -#' @title Extract specific dataset from austraits object for versions >3.0.2 -#' @rdname extract_dataset - -extract_dataset2 <- function(austraits, dataset_id){ - austraits$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - ret <- list() - for(v in c("traits", "locations", "contexts", "methods", - "excluded_data", "taxonomic_updates", "contributors")) - ret[[v]] <- austraits[[v]][ austraits[[v]][["dataset_id"]] %in% dataset_id,] - # NB: can't use dplyr::filter in the above as it doesn't behave when the variable name is the same as a column name - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - - ret[["definitions"]] <- austraits[["definitions"]] - ret[["build_info"]] <- austraits[["build_info"]] - ret[["schema"]] <- austraits[["schema"]] - - keys <- dplyr::union(ret$methods$source_primary_key, - ret$methods$source_secondary_key %>% strsplit("; ") %>% unlist()) %>% - unique() %>% stats::na.omit() %>% as.character() - - ret[["sources"]] <- austraits$sources[keys] - - ret[["sources"]] <- austraits[["sources"]][keys] - - assertthat::are_equal(sort(names(austraits)), sort(names(ret))) - - ret[names(austraits)] - - # Assign class - attr(ret, "class") <- "austraits" - - ret -} diff --git a/R/extract_taxa.R b/R/extract_taxa.R index d8737ed..8145ab8 100644 --- a/R/extract_taxa.R +++ b/R/extract_taxa.R @@ -1,169 +1,54 @@ -#' @title Extract data for one specific taxa +#' @title Extract all data for specific taxa #' -#' @description Function to subset of all data associated with a particular dataset from austraits -#' @param austraits austraits list object -#' @param family character string of family -#' @param genus character string of genus -#' @param taxon_name character string of taxon name -#' @return A large list of tibbles containing all austraits information for specificied taxa +#' @description Function to subset of all data associated with a particular taxon from a traits.build relational database. +#' +#' @param database traits.build database (list object) +#' @param family character string of family or families +#' @param genus character string of genus or genera +#' @param taxon_name character string of taxon name(s) +#' @return List of tibbles containing all traits.build data and metadata for the specified taxa. +#' @details +#' `extract_taxa` has been developed to extract data for specific taxa from databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build-book) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/database](https://github.com/traitecoevo/database) for how to install old versions of the package or download a newer version of the database. #' #' @examples #' \dontrun{ -#'extract_taxa(austraits, family = "Proteaceae") -#'extract_taxa(austraits, genus = "Acacia") +#'extract_taxa(database = austraits, family = "Proteaceae") +#'extract_taxa(database = austraits, genus = "Acacia") #' } #' @author Fonti Kar - f.kar@unsw.edu.au #' @export -extract_taxa <- function(austraits, family = NULL, genus = NULL, taxon_name = NULL){ - # Switch for different versions - version <- what_version(austraits) +extract_taxa <- function(database, family = NULL, genus = NULL, taxon_name = NULL){ + # Check compatability + status <- check_compatibility(database, single_table_allowed = TRUE) - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = extract_taxa2(austraits, family, genus, taxon_name), - 'old' = extract_taxa1(austraits, family, genus, taxon_name), - ) -} - - -#'Extract taxa >3.0.2 -#' @noRd -#' @keywords internal -extract_taxa2 <- function(austraits, family = NULL, genus = NULL, taxon_name = NULL){ - - ret <- austraits + # If compatible + if(!status){ + function_not_supported(database) + } + ret <- database if(missing(family) & missing(genus) & missing(taxon_name)){ abort("Either `family`, `genus` or `taxon_name`, must be supplied!") } if( ! is.null(family) ){ - # Retrieving all taxon name that falls under family - target_in <- stringr::str_which(austraits$taxa$family, paste(family, collapse = "|")) - target_taxa <- austraits$taxa %>% dplyr::slice(target_in) %>% dplyr::pull(taxon_name) + return(extract_data(database, "taxa", "family", col_value = family)) } if( ! is.null(genus) ){ - # Retrieving all taxon name that falls under genus - target_in <- stringr::str_which(austraits$taxa$genus, paste(genus, collapse = "|")) - target_taxa <- austraits$taxa %>% dplyr::slice(target_in) %>% dplyr::pull(taxon_name) + return(extract_data(database, "taxa", "genus", col_value = genus)) } - if( ! is.null(taxon_name)){ - target_taxa <- taxon_name - } - - # Extract data for target_sp - ret[["traits"]] <- ret[["traits"]] %>% - dplyr::filter(taxon_name %in% target_taxa) - - dataset_id <- ret[["traits"]][["dataset_id"]] %>% unique() %>% sort() - - # Dataset specific tables - for(v in c("locations", "contexts", "contributors", "methods")){ - ret[[v]] <- austraits[[v]][ austraits[[v]][["dataset_id"]] %in% dataset_id,] - } - # NB: can't use dplyr::filter in the above as it doesn't behave when the variable name is the same as a column name - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% target_taxa) - - ret[["taxonomic_updates"]] <- austraits[["taxonomic_updates"]] %>% dplyr::filter(taxon_name %in% target_taxa) - # Fix formatting for dataset ids - ret$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - ret[["excluded_data"]] <- austraits[["excluded_data"]] %>% dplyr::filter(taxon_name %in% target_taxa) - - ret[["definitions"]] <- austraits[["definitions"]] - - ret[["build_info"]] <- austraits[["build_info"]] - - # if numeric, convert to numeric - suppressWarnings( - ret[["traits"]][["value"]] <- ifelse(! is.na(ret[["traits"]][["unit"]]), - as.numeric(ret[["traits"]][["value"]]), - ret[["traits"]][["value"]]) - - ) - - # Assign class - attr(ret, "class") <- "austraits" - - ret -} - - -#'Extract taxa <=3.0.2 -#' @noRd -#' @keywords internal -extract_taxa1 <- function(austraits, family = NULL, genus = NULL, taxon_name = NULL){ - - ret <- austraits - - if(missing(family) & missing(genus) & missing(taxon_name)){ - abort("Either `family`, `genus` or `taxon_name`, must be supplied!") - } - - if( ! is.null(family) ){ - # Retrieving all taxon name that falls under family - target_in <- stringr::str_which(austraits$taxa$family, paste(family, collapse = "|")) - target_taxa <- austraits$taxa %>% dplyr::slice(target_in) %>% dplyr::pull(taxon_name) - } - - if( ! is.null(genus) ){ - # Retrieving all taxon name that falls under genus - target_in <- stringr::str_which(austraits$taxa$genus, paste(genus, collapse = "|")) - target_taxa <- austraits$taxa %>% dplyr::slice(target_in) %>% dplyr::pull(taxon_name) - } - - if( ! is.null(taxon_name)){ - target_taxa <- taxon_name - } - - # Extract data for target_sp - ret[["traits"]] <- ret[["traits"]] %>% - dplyr::filter(taxon_name %in% target_taxa) - - ids <- ret[["traits"]][["dataset_id"]] %>% unique() %>% sort() - - ret[["sites"]] <- austraits[["sites"]] %>% dplyr::filter(site_name %in% ret[["traits"]][["site_name"]], dataset_id %in% ids) - - ret[["contexts"]] <- austraits[["contexts"]] %>% dplyr::filter(context_name %in% ret[["traits"]][["context_name"]], dataset_id %in% ids) - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - - ret[["taxonomic_updates"]] <- austraits[["taxonomic_updates"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - # Fix formatting for dataset ids - ret$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - ret[["excluded_data"]] <- austraits[["excluded_data"]] %>% dplyr::filter(taxon_name %in% target_taxa) - - ret[["contributors"]] <- austraits[["contributors"]] %>% dplyr::filter(dataset_id %in% ids) - - ret[["methods"]] <- austraits[["methods"]] %>% dplyr::filter(dataset_id %in%ids) - - ret[["definitions"]] <- austraits[["definitions"]] - - ret[["build_info"]] <- austraits[["build_info"]] - - # if numeric, convert to numeric - suppressWarnings( - ret[["traits"]][["value"]] <- ifelse(! is.na(ret[["traits"]][["unit"]]), - as.numeric(ret[["traits"]][["value"]]), - ret[["traits"]][["value"]]) - - ) - - # Assign class - attr(ret, "class") <- "austraits" - - ret + if( ! is.null(taxon_name)) + return(extract_data(database, "traits", "taxon_name", col_value = taxon_name)) } diff --git a/R/extract_trait.R b/R/extract_trait.R index 1591c83..b304643 100644 --- a/R/extract_trait.R +++ b/R/extract_trait.R @@ -1,154 +1,44 @@ -#' @title Extract data for specific traits +#' @title Extract all data for specific traits #' -#' @description Function to subset of all data associated with a particular dataset from austraits -#' @usage extract_trait(austraits, trait_names, taxon_names) -#' @param austraits - A large list of tibbles built from austraits -#' @param trait_names - character string of trait that will be extracted -#' @param taxon_names - optional argument -#' @return A large list of tibbles containing all austraits information for one particular dataset +#' @description Function to subset all data associated with a particular trait from a traits.build relational database. +#' +#' @usage extract_trait(database, trait_names, taxon_names) +#' @param database traits.build database (list object) +#' @param trait_names character string of trait(s) for which data will be extracted +#' @param taxon_names optional argument, specifying taxa for which data will be extracted +#' @return List of tibbles containing all traits.build data and metadata for the specified trait(s). +#' @details +#' `extract_trait` has been developed to extract data for specific traits from databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. #' #' @examples #' \dontrun{ -#'extract_trait(austraits, "wood_density", taxon_name = "Acacia celsa") +#'extract_trait(database = austraits, trait_names = "wood_density", taxon_names = "Acacia celsa") #' } #' @author Daniel Falster - daniel.falster@unsw.edu.au #' @export -extract_trait <- function(austraits, trait_names, taxon_names=NULL) { - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = extract_trait2(austraits, trait_names, taxon_names), - 'old' = extract_trait1(austraits, trait_names, taxon_names), - ) -} +extract_trait <- function(database, trait_names, taxon_names=NULL) { + # Check compatability + status <- check_compatibility(database, single_table_allowed = TRUE) + + # If compatible + if(!status){ + function_not_supported(database) + } -#' @title Extract specific trait data from austraits object for versions <=3.0.2 -#' @noRd -#' @keywords internal -extract_trait1 <- function(austraits, trait_names, taxon_names=NULL) { - - ret <- austraits - - ret[["traits"]] <- austraits[["traits"]] %>% - dplyr::filter(trait_name %in% trait_names) - - if(!is.null(taxon_names)){ - ret[["traits"]] <- ret[["traits"]] %>% - dplyr::filter(taxon_name %in% taxon_names) - } - - ids <- ret[["traits"]][["dataset_id"]] %>% unique() %>% sort() - - ret[["sites"]] <- austraits[["sites"]] %>% dplyr::filter(site_name %in% ret[["traits"]][["site_name"]], dataset_id %in% ids) - - ret[["contexts"]] <- austraits[["contexts"]] %>% dplyr::filter(context_name %in% ret[["traits"]][["context_name"]], dataset_id %in% ids) - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - ret[["taxonomic_updates"]] <- austraits[["taxonomic_updates"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - - ret$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - - ret[["excluded_data"]] <- austraits[["excluded_data"]][austraits[["excluded_data"]][["trait_name"]] %in% trait_names,] + ret <- extract_data(database, "traits", "trait_name", col_value = trait_names) if(!is.null(taxon_names)) - ret[["excluded_data"]] <- ret[["excluded_data"]] %>% dplyr::filter(taxon_name %in% taxon_names) - - - ret[["contributors"]] <- austraits[["contributors"]] %>% dplyr::filter(dataset_id %in% ids) - - ret[["methods"]] <- austraits[["methods"]] %>% dplyr::filter(dataset_id %in%ids, trait_name %in% ret[["traits"]][["trait_name"]]) - - ret[["definitions"]] <- austraits[["definitions"]] - ret[["build_info"]] <- austraits[["build_info"]] - - # if numeric, convert to numeric - if(!is.na(ret[["traits"]][["unit"]][1])){ - suppressWarnings(ret[["traits"]][["value"]] <- as.numeric(ret[["traits"]][["value"]])) - } - - - keys <- dplyr::union(ret$methods$source_primary_key, - ret$methods$source_secondary_key %>% strsplit("; ") %>% unlist()) %>% - unique() %>% stats::na.omit() %>% as.character() - - ret[["sources"]] <- austraits$sources[keys] - - ret[names(austraits)] - - # Assign class - attr(ret, "class") <- "austraits" - - ret -} - -#' @title Extract specific trait data from austraits object for versions >3.0.2 -#' @noRd -#' @keywords internal -extract_trait2 <- function(austraits, trait_names, taxon_names=NULL) { - - ret <- austraits - - # Traits table - ret[["traits"]] <- austraits[["traits"]] %>% - dplyr::filter(trait_name %in% trait_names) - - # If taxon_name supplied, further filter traits table - if(!is.null(taxon_names)){ - ret[["traits"]] <- ret[["traits"]] %>% - dplyr::filter(taxon_name %in% taxon_names) - } - - dataset_id <- ret[["traits"]][["dataset_id"]] %>% unique() %>% sort() - - # Dataset specific tables - for(v in c("locations", "contexts", "contributors")){ - ret[[v]] <- austraits[[v]][ austraits[[v]][["dataset_id"]] %in% dataset_id,] - } - # NB: can't use dplyr::filter in the above as it doesn't behave when the variable name is the same as a column name - - ret[["taxa"]] <- austraits[["taxa"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - ret[["taxonomic_updates"]] <- austraits[["taxonomic_updates"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]]) - - # Fix formating for datasets - ret$taxonomic_updates <- - tidyr::separate_rows(austraits$taxonomic_updates, dataset_id, sep=" ") - - ret[["excluded_data"]] <- austraits[["excluded_data"]] %>% dplyr::filter(taxon_name %in% ret[["traits"]][["taxon_name"]], trait_name %in% trait_names) - - ret[["methods"]] <- austraits[["methods"]] %>% dplyr::filter(dataset_id %in% dataset_id, trait_name %in% trait_names) - - # Tables that never change - ret[["definitions"]] <- austraits[["definitions"]] - ret[["build_info"]] <- austraits[["build_info"]] - ret[["schema"]] <- austraits[["schema"]] - - # if numeric, convert to numeric - if(!is.na(ret[["traits"]][["unit"]][1])){ - suppressWarnings(ret[["traits"]][["value"]] <- as.numeric(ret[["traits"]][["value"]])) - } - - - keys <- dplyr::union(ret$methods$source_primary_key, - ret$methods$source_secondary_key %>% strsplit("; ") %>% unlist()) %>% - unique() %>% stats::na.omit() %>% as.character() - - ret[["sources"]] <- austraits$sources[keys] - - ret[names(austraits)] - - # Assign class - attr(ret, "class") <- "austraits" + ret <- extract_data(ret, "traits", "taxon_name", col_value = taxon_names) - ret + return(ret) } diff --git a/R/flatten_database.R b/R/flatten_database.R new file mode 100644 index 0000000..9789a7d --- /dev/null +++ b/R/flatten_database.R @@ -0,0 +1,53 @@ +#' Create combined traits.build table +#' +#' Create a single database output that merges together the information +#' in all relational tables within a traits.build database. +#' Trait measurements are still output in long format (1 row per trait value), +#' but all measurement-related metadata (methods, location properties, context properties, contributors) +#' are now included as additional columns in a single table. +#' +#' @param database traits.build database (list object) +#' @param format A parameter for the locations, contexts and data contributors tables specifying how data are packed. +#' All three can be formatted as a single compacted column(s) will have a human readable column ("single_column_pretty") +#' or using json ("single_column_json") syntax. For location properties or context properties there is also +#' the option to add each `location_property` or `context_property` to the traits table as its own column ("many_columns"); +#' the contributors column defaults to "single_column_pretty" when this option is selected. +#' @param vars List specifying which columns or properties to include from each table. The detail is for all columns/properties to be included. +#' @param include_description A logical indicating whether to include (TRUE) or omit (FALSE) the context_property descriptions; defaults to TRUE. +#' +#' @return A table combining information in 7 traits.build relational tables: traits, locations, contexts, methods, taxa, taxonomic_updates, and contributors +#' @export +#' +#' @usage flatten_database(database, format, vars, include_description) +#' +flatten_database <- function(database, + format = "single_column_pretty", + vars = list( + location = "all", + context = "all", + contributors = "all", + taxonomy = "all", + taxonomic_updates = "all", + methods = setdiff(names(database$methods), c("data_collectors")) + ), + include_description = TRUE + ) { + # Since `data_collectors` is also merged into the combined_table via the contributors tibble, we don't want the information twice. + + if (format == "many_columns") { + format_contributors = "single_column_pretty" + } else { + format_contributors = format + } + + combined_table_relational <- database %>% + join_location_coordinates() %>% + join_location_properties(format = format, vars = vars$location) %>% + join_context_properties(format = format, vars = vars$context, include_description = TRUE) %>% + join_methods(vars = vars$methods) %>% + join_contributors(format = format_contributors, vars = vars$contributors) %>% + join_taxa(vars = vars$taxonomy) %>% + join_taxonomic_updates(vars = vars$taxonomic_updates) + + combined_table <- combined_table_relational$traits +} diff --git a/R/join_.R b/R/join_.R new file mode 100644 index 0000000..729a628 --- /dev/null +++ b/R/join_.R @@ -0,0 +1,550 @@ +#' @title Joining location coordinates to traits table +#' @description Function to merge geographic coordinates (latitude/longitude) +#' stored in the locations table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @return traits.build list object, but with additional fields (columns) +#' for latitude and longitude appended to `traits` dataframe +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @examples +#' \dontrun{ +#' (database %>% join_location_coordinates)$traits +#' } +#' +#' @export +join_location_coordinates <- function(database) { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + location_coordinates <- + database$locations %>% + dplyr::filter(location_property %in% c("latitude (deg)", "longitude (deg)")) %>% + tidyr::pivot_wider(names_from = location_property, values_from = value) + + # variables to join_ by depends on if location_name already in traits table + # from joining coordinates for instances + join_vars <- intersect(names(database$traits), c("dataset_id", "location_id", "location_name")) + + if (any(stringr::str_detect(names(location_coordinates), "latitude "))) { + database$traits <- + database$traits %>% + dplyr::left_join(by = join_vars, location_coordinates) + + } else { + database$traits <- + database$traits %>% + dplyr::mutate( + location_name = NA_character_, + `latitude (deg)` = NA_character_, + `longitude (deg)` = NA_character_, + ) + } + + database +} + + +#' @title Joining taxonomy to traits table + +#' @description Function to merge metadata from the taxa table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param vars Columns from the taxa table to be joined to the traits table, defaulting to c("family", "genus", "taxon_rank", "establishment_means"). +#' +#' @return traits.build list object, but with additional fields (columns) for the specified variables from the taxa table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' #Append taxonomic details +#' (database %>% join_taxa)$traits +#' } +join_taxa <- function(database, + vars = c("family", "genus", "taxon_rank", "establishment_means")) { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # If all columns to be added, create `vars` vector + if (vars[1] == "all" & length(vars == 1)){ + vars <- names(database$taxa) + } + + # Join selected columns to traits table + database$traits <- + database$traits %>% + dplyr::left_join(by="taxon_name", database$taxa %>% dplyr::select("taxon_name", tidyselect::any_of(vars))) + + database +} + + +#' @title Joining taxonomic updates information to traits table +#' +#' @description Function to merge metadata from the taxonomic_updates table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param vars Columns from the taxa table to be joined to the traits table, defaulting to c("aligned_name"). +#' +#' @return traits.build list object, but with additional fields (columns) for the specified variables from the taxonomic_updates table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' #Append taxonomic update details +#' (database %>% join_taxonomic_updates)$traits +#' } +join_taxonomic_updates <- function(database, vars = c("aligned_name")) { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # If all columns to be added, create `vars` vector + if (vars[1] == "all" & length(vars == 1)){ + vars <- names(database$taxonomic_updates) + } + + # Join selected columns to traits table + database$traits <- + database$traits %>% + dplyr::left_join(by = c("taxon_name", "dataset_id", "original_name"), + database$taxonomic_updates %>% + dplyr::select("taxon_name", "dataset_id", "original_name", + tidyselect::any_of(vars))) + + database +} + +#' @title Joining methodological information to traits table +#' +#' @description Function to merge metadata from the methods table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param vars Columns from the taxa table to be joined to the traits table, defaulting to c("methods"). +#' +#' @return traits.build list object, but with additional fields (columns) for the specified variables from the methods table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' (database %>% join_methods)$traits +#' } +join_methods <- function(database, vars = c("methods")) { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # If all columns to be added, create `vars` vector + if (vars[1] == "all" & length(vars == 1)){ + vars <- names(database$methods) + } + + # Join selected columns to traits table + database$traits <- + database$traits %>% + dplyr::left_join(by=c("dataset_id", "trait_name", "method_id"), + database$methods %>% + dplyr::select(c("dataset_id", "trait_name", "method_id"), tidyselect::any_of(vars)) %>% + dplyr::distinct() + ) + + database +} + + +#' @title Joining data contributor metadata to traits table +#' +#' @description Function to merge metadata from the data contributors table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param format Specifies whether metadata from the contributors table is output in a human readable format ("single_column_pretty"; default) or using json syntax ("single_column_json"). +#' @param vars Columns from the taxa table to be joined to the traits table, defaulting to all columns (vars = "all"). +#' +#' @return traits.build list object, but with additional fields (columns) for the specified variables from the data contributors table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' (database %>% join_contributors(format = "single_column_pretty", +#' vars = c("last_name", "first_name", "ORCID")))$traits +#' } +join_contributors <- function(database, + format = "single_column_pretty", + vars = "all") { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # Work out which vars to retain and create a dataframe for compacting + if (vars[1] == "all") { + contributors_tmp <- database$contributors + } else { + # Create vector that is combination of selected columns and required columns + vars_tmp <- c("dataset_id", "last_name", "given_name", vars) + # Determine which columns aren't wanted + vars_remove <- setdiff(names(database$contributors), vars_tmp) + # Remove unwanted columns from contributors dataframe + contributors_tmp <- database$contributors %>% dplyr::select(-dplyr::any_of(vars_remove)) + } + + # Different options for how data are compacted and joined depending on `format` argument + if (format == "single_column_pretty") { + # collapse all metadata for a single contributor into a single cell + contributor_metadata <- + contributors_tmp %>% + tidyr::pivot_longer(cols = 4:ncol(contributors_tmp)) %>% + dplyr::filter(!is.na(value)) %>% + dplyr::group_by(dataset_id, last_name, given_name) %>% + dplyr::mutate(contributor = paste0(paste0(name, "==", value), collapse = " \\ "))%>% + dplyr::select(-name, -value) %>% + dplyr::distinct() %>% + dplyr::ungroup() + + # Merge in contributor metadata and paste together with name + compacted_contributors_column <- + contributors_tmp %>% + dplyr::left_join(contributor_metadata, + by = c("dataset_id", "last_name", "given_name")) %>% + dplyr::mutate( + data_contributors = ifelse(is.na(contributor), + paste0(last_name, ", ", given_name), + paste0(last_name, ", ", given_name, " <<", contributor, ">>"))) %>% + dplyr::select(dataset_id, data_contributors) %>% + # Collapse metadata for all data contributors associated with a dataset into a single cell + dplyr::group_by(dataset_id) %>% + dplyr::mutate(data_contributors = paste0(data_contributors, collapse = ";; ")) %>% + dplyr::ungroup() %>% + dplyr::distinct() + + } else if (format == "single_column_json") { + + compacted_contributors_column <- + contributors_tmp %>% + tidyr::nest(-dplyr::all_of("dataset_id")) %>% + dplyr::mutate(data_contributors = purrr::map_chr(data, jsonlite::toJSON)) %>% + dplyr::select(-dplyr::any_of("data")) %>% + dplyr::ungroup() + } + + database$traits <- database$traits %>% + dplyr::left_join(by = c("dataset_id"), compacted_contributors_column) + + database +} + + +#' @title Joining location properties to traits table +#' +#' @description Function to merge metadata from the locations table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param format Specifies whether metadata from the locations is output in a human readable format ("single_column_pretty"; default), with each location property added as a separate column ("many_columns") or using json syntax ("single_column_json"). +#' @param vars Location properties for which data is to be appended to the traits table, defaulting to all location properties (vars = "all"). +#' +#' @return traits.build list object, but location properties from the locations table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' (database %>% join_location_properties(format = "single_column_pretty", vars = "all"))$traits +#' } +join_location_properties <- function(database, + format = "single_column_pretty", + vars = "all") { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # If all location properties to be added, create `vars` vector that is unique list + # of location properties in the database + if (vars[1] == "all") { + + vars_tmp <- database$locations %>% + dplyr::distinct(location_property) %>% + dplyr::filter(!location_property %in% c("latitude (deg)", "longitude (deg)")) + + vars <- vars_tmp$location_property + } + + # If latitude, longitude present in vars list, remove them + vars <- setdiff(vars, c("latitude (deg)", "longitude (deg)")) + + locations <- + database$locations %>% + dplyr::filter(location_property %in% vars) + + # Variables to join_ by depends on if location_name already in traits table + # from joining coordinates for instances + join_vars <- intersect(names(database$traits), c("dataset_id", "location_id", "location_name")) + + # Different options for how data are compacted and joined depending on `format` argument + if (format == "many_columns") { + + # Pivot wider, so each `location_property` in its own column + locations <- + locations %>% + dplyr::mutate(location_property = paste0("location_property: ", location_property)) %>% + tidyr::pivot_wider(names_from = location_property) + + # Join locations, based on appropriate columns + database$traits <- + database$traits %>% + dplyr::left_join(by = join_vars, locations) + + } else if (format == "single_column_pretty") { + + # Merge each location property and its corresponding value + compacted_locations_column <- + locations %>% + dplyr::mutate(location_properties = paste0(location_property, "==", value)) %>% + dplyr::select(dplyr::all_of(c("dataset_id", "location_id", "location_name", "location_properties"))) %>% + dplyr::group_by(dataset_id, location_id, location_name) %>% + # collapse all location properties associated with a measurement into a single cell + dplyr::mutate(location_properties = paste0(location_properties, collapse = ";; ")) %>% + dplyr::ungroup() %>% + dplyr::distinct() + + database$traits <- + database$traits %>% + dplyr::left_join(by = join_vars, compacted_locations_column) + + } else if (format == "single_column_json") { + + compacted_locations_column <- + locations %>% + tidyr::nest(data = -dplyr::all_of(c("dataset_id", "location_id"))) %>% + dplyr::mutate(location_properties = purrr::map_chr(data, jsonlite::toJSON)) %>% + dplyr::select(-dplyr::any_of("data")) %>% + dplyr::ungroup() + + database$traits <- database$traits %>% + dplyr::left_join(by = join_vars, compacted_locations_column) + + } + + database +} + +#' @title Joining context properties to traits table +#' +#' @description Function to merge metadata from the contexts table of a traits.build database into the core traits table. +#' +#' @param database traits.build database (list object) +#' @param format Specifies whether metadata from the contexts is output in a human readable format ("single_column_pretty"; default), with each context property added as a separate column ("many_columns") or using json syntax ("single_column_json"). +#' @param vars Location properties for which data is to be appended to the traits table, defaulting to all context properties (vars = "all"). +#' @param include_description A logical indicating whether to include (TRUE) or omit (FALSE) the context_property descriptions. +#' +#' @return traits.build list object, but context properties from the contexts table appended to the traits table. +#' @details +#' the `join_` functions have been developed to join relational tables for databases built using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' +#' @export +#' +#' @examples +#' \dontrun{ +#' (database %>% join_context_properties( +#' format = "many_columns", vars = "all", include_description = TRUE))$traits +#' } +join_context_properties <- function(database, + format = "single_column_pretty", + vars = "all", + include_description = TRUE) { + + # Check compatibility + if(!check_compatibility(database)){ + function_not_supported(database) + } + + # If all context properties to be added, create `vars` vector that is unique list + # of context properties in the database + if (vars[1] == "all") { + vars <- database$contexts$context_property %>% unique() + } + + # Create dataframe of contexts to use & add `context_property:` to context properties + contexts_tmp <- + database$contexts %>% + dplyr::filter(context_property %in% vars) %>% + dplyr::mutate(context_property = paste0(category, ": ", context_property)) + + # From here format depends on desired output + if (format == "many_columns") { + contexts_tmp <- + contexts_tmp %>% + dplyr::mutate( + value = ifelse( + is.na(description) | include_description == FALSE, + value, + paste0(value, " <<", description, ">>")) + ) %>% + dplyr::select(-dplyr::all_of(c("description", "category"))) %>% + tidyr::separate_longer_delim(link_vals, ", ") + + pivot <- TRUE + } else if (format == "single_column_pretty") { + contexts_tmp <- + contexts_tmp %>% + dplyr::mutate( + value = ifelse( + !is.na(description) & include_description, + paste0(context_property, "==", value, " <<", description, ">>"), + paste0(context_property, "==", value)) + ) %>% + dplyr::select(-dplyr::all_of(c("description", "context_property", "category"))) %>% + tidyr::separate_longer_delim(link_vals, ", ") %>% + dplyr::distinct() %>% + dplyr::group_by(dataset_id, link_id, link_vals) %>% + dplyr::mutate(value = paste0(value, collapse = ";; ")) %>% + dplyr::distinct() %>% + dplyr::ungroup() + + pivot <- FALSE + } else if (format == "single_column_json") { + + contexts_tmp <- + contexts_tmp %>% + tidyr::separate_longer_delim(link_vals, ", ") %>% + dplyr::distinct() %>% + dplyr::mutate(description = ifelse(!is.na(description) & include_description, description, NA)) %>% + tidyr::nest(data = -dplyr::all_of(c("dataset_id", "link_id", "link_vals"))) %>% + dplyr::mutate(value = purrr::map_chr(data, jsonlite::toJSON)) %>% + dplyr::select(-dplyr::any_of("data")) %>% + dplyr::ungroup() + + pivot <- FALSE + + } else { + stop("format not supported: ", format) + } + + # Merge contexts to database$traits + + # Defines a function to further reformat specific columns of the context table + reformat_contexts <- function(data, context_id, pivot) { + + data <- + data %>% + dplyr::filter(link_id == context_id) + + if(pivot) { + data <- tidyr::pivot_wider(data, names_from = context_property, values_from = value) + } + + data <- + data %>% + dplyr::select(-link_id) %>% + dplyr::distinct(dataset_id, link_vals, .keep_all = TRUE) + + names(data)[which(names(data) == "value")] <- gsub("_id", "_properties", context_id, fixed = TRUE) + names(data)[which(names(data) == "link_vals")] <- context_id + + data + } + + + database$traits <- + database$traits %>% + dplyr::left_join( + by = c("dataset_id", "treatment_context_id"), + reformat_contexts(contexts_tmp, "treatment_context_id", pivot) + ) %>% + dplyr::left_join( + by = c("dataset_id", "plot_context_id"), + reformat_contexts(contexts_tmp, "plot_context_id", pivot) + ) %>% + dplyr::left_join( + by = c("dataset_id", "entity_context_id"), + reformat_contexts(contexts_tmp, "entity_context_id", pivot) + ) %>% + dplyr::left_join( + by = c("dataset_id", "temporal_context_id"), + reformat_contexts(contexts_tmp, "temporal_context_id", pivot) + ) %>% + dplyr::left_join( + by = c("dataset_id", "method_context_id"), + reformat_contexts(contexts_tmp, "method_context_id", pivot) + ) + + database + +} + diff --git a/R/join_all.R b/R/join_all.R deleted file mode 100644 index 1ad1a4b..0000000 --- a/R/join_all.R +++ /dev/null @@ -1,285 +0,0 @@ -#' @title Join study details into main `traits` dataset -#' @description Function to append all study information (method, location, taxonomic, context) variables into trait database -#' @param austraits dataframe generated by austraits build -#' @param ... arguments passed to `vars` to subset the columns -#' @return austraits list object, but with additional variables appended to `traits` dataframe -#' @rdname join_all - -#' @examples -#' \dontrun{ -#' austraits$traits -#' -#' #Append locations data -#' (austraits %>% join_locations)$traits -#' -#' #Append contexts -#' (austraits %>% join_contexts)$traits -#' -#' # Append methods -#' (austraits %>% join_methods(vars = c("method_id")))$traits -#' -#' #Append taxonomic details -#' (austraits %>% join_taxonomy)$traits -#' -#' #Append all information -#' (austraits %>% join_all)$traits -#' } -#' @author Daniel Falster - daniel.falster@unsw.edu.au -#' @export - - -join_all <- function(austraits) { - austraits %>% - join_locations() %>% - join_taxonomy() %>% - join_methods() -} - -#' @title Joining taxonomic information to traits table -#' @export - -#' @rdname join_all - -join_taxonomy <- function(austraits, ...) { - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = join_taxonomy2(austraits, ...), - 'old' = join_taxonomy1(austraits, ...), - ) -} - -#' @title Joining taxonomic info for AusTraits versions <= 3.0.2 -#' @noRd -#' @keywords internal - -join_taxonomy1 <- function(austraits, vars = c("family", "genus", "taxonRank", "acceptedNameUsageID")) { - austraits$traits <- austraits$traits %>% - dplyr::left_join(by="taxon_name", austraits$taxa %>% dplyr::select("taxon_name", tidyselect::any_of(vars))) - - austraits -} - -#' @title Joining taxonomic info for AusTraits versions > 3.0.2 -#' @noRd -#' @keywords internal - -join_taxonomy2 <- function(austraits, vars = c("family", "genus", "taxon_rank", "establishment_means")) { - austraits$traits <- austraits$traits %>% - dplyr::left_join(by="taxon_name", austraits$taxa %>% dplyr::select("taxon_name", tidyselect::any_of(vars))) - - austraits -} - -#' @title Joining methodological information to traits table - -#' @export -#' @rdname join_all - -join_methods <- function(austraits, ...) { - - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) == "5-series"){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = join_methods2(austraits, ...), - 'old' = join_methods1(austraits, ...), - ) -} - -#' @title Joining methods info for AusTraits versions > 3.0.2 -#' @noRd -#' @keywords internal -join_methods2 <- function(austraits, vars = c("methods", "year_collected_start", "year_collected_end", "collection_type")) { - austraits$methods %>% - dplyr::select(c("dataset_id", "trait_name", "method_id"), tidyselect::any_of(vars)) %>% - dplyr::distinct() -> methods - - austraits$traits <- austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "trait_name", "method_id"), - methods, relationship = "many-to-many") - - austraits -} - -#' @title Joining methods info for AusTraits versions<== 3.0.2 -#' @noRd -#' @keywords internal -join_methods1 <- function(austraits, vars = c("methods", "year_collected_start", "year_collected_end", "collection_type")) { - austraits$methods %>% - dplyr::select(c("dataset_id", "trait_name"), tidyselect::any_of(vars)) %>% - dplyr::distinct() -> methods - - austraits$traits <- austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "trait_name"), - methods, relationship = "many-to-many") - - austraits -} -#' @title Joining location information to traits table -#' @export - -#' @rdname join_all - -join_locations <- function(austraits, ...) { - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = join_locations2(austraits, ...), - 'old' = join_locations1(austraits, ...), - ) -} - - -#' @title Joining location info for AusTraits versions <= 3.0.2 -#' @noRd -#' @keywords internal -join_locations1 <- function(austraits, vars = c("longitude (deg)","latitude (deg)")) { - - sites <- - austraits$sites %>% - dplyr::filter(site_property %in% vars) %>% - tidyr::pivot_wider(names_from = site_property, values_from = value) - - austraits$traits <- austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "site_name"), sites) - - austraits -} - -#' @title Joining location info for AusTraits versions <= 3.0.2 -#' @description `r lifecycle::badge('deprecated')` -#' Joining location info for AusTraits versions <= 3.0.2 -#' @param austraits austraits object -#' @param vars variables from site table to join -#' @export - -join_sites <- function(austraits, vars = c("longitude (deg)","latitude (deg)")) { - .Deprecated("join_locations") - - join_locations1(austraits, vars = c("longitude (deg)","latitude (deg)")) -} - -#' @title Joining location info for AusTraits versions > 3.0.2 -#' @noRd -#' @keywords internal -join_locations2 <- function(austraits, vars = c("longitude (deg)","latitude (deg)")) { - sites <- - austraits$locations %>% - dplyr::filter(location_property %in% vars) %>% - tidyr::pivot_wider(names_from = location_property) - - austraits$traits <- austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "location_id"), sites) - - austraits -} - - -#' @export -#' @rdname join_all - -join_contexts <- function(austraits,...){ - # Switch for different versions - version <- what_version(austraits) - - if(what_version(austraits) %in% c("4-series", "5-series")){ - version <- "new" - } else - version <- "old" - - switch (version, - 'new' = join_contexts2(austraits, ...), - 'old' = join_contexts1(austraits, ...), - ) -} - -#' @title Joining location info for AusTraits versions > 3.0.2 -#' @noRd -#' @keywords internal -join_contexts2 <- function(austraits, collapse_context = FALSE){ - - traits2 <- split(austraits$traits, austraits$traits$dataset_id) - contexts2 <- split(austraits$contexts, austraits$contexts$dataset_id) - - traits_vars <- names(austraits$traits) - - problem_studies <- c("Hall_1981") - - for(id in names(traits2)) { - - if(!is.null(contexts2[[id]][1]) & ! (id %in% problem_studies)) { - - context_ids <- - unique(contexts2[[id]]$link_id) - - for(v in context_ids[!is.na(context_ids)]) { - - context_sub <- - contexts2[[id]] %>% - dplyr::select(-dplyr::any_of(c("category", "description"))) %>% - dplyr::filter(link_id == v) %>% - tidyr::separate_rows(link_vals) %>% - tidyr::pivot_wider(values_from = value, names_from = context_property) %>% - tidyr::pivot_wider(names_from = link_id, values_from = link_vals) - - traits2[[id]] <- - dplyr::left_join(by = c("dataset_id", v), - traits2[[id]], - context_sub - ) - } - - if(collapse_context == TRUE){ - context_text <- - traits2[[id]] %>% - dplyr::select(-dplyr::any_of(traits_vars)) %>% collapse_cols() - - traits2[[id]] <- traits2[[id]] %>% - dplyr::mutate(context = context_text) %>% - dplyr::select(dplyr::any_of(traits_vars), context) - } - } - } - - austraits$traits <- traits2 %>% dplyr::bind_rows() - - austraits -} - -#' @title Joining contexts info for AusTraits versions <= 3.0.2 -#' @noRd -#' @keywords internal - -join_contexts1 <- function(austraits) { - - if(nrow(austraits$contexts) == 0) - return (austraits) - - contexts <- - austraits$contexts %>% - tidyr::pivot_wider(names_from = context_property, values_from = value) - - austraits$traits <- austraits$traits %>% - dplyr::left_join(by=c("dataset_id", "context_name"), contexts) - - austraits -} - diff --git a/R/load_austraits.R b/R/load_austraits.R index 80a26a5..2f332a3 100644 --- a/R/load_austraits.R +++ b/R/load_austraits.R @@ -62,7 +62,7 @@ load_austraits <- function(doi = NULL, version = NULL, path = "data/austraits", version_name <- paste0("v", version) # Getting specific version - id <- ret[which(ret$version == version), "id"] |> as.character() + id <- ret[which(ret$version == version), "id"] %>% as.character() target <- res$hits$hits$files[[version_name]] @@ -82,7 +82,7 @@ load_austraits <- function(doi = NULL, version = NULL, path = "data/austraits", data <- readRDS(file_nm) # Assign class - attr(data, "class") <- "austraits" + attr(data, "class") <- "traits.build" data } @@ -90,7 +90,8 @@ load_austraits <- function(doi = NULL, version = NULL, path = "data/austraits", #' Load the austraits.json #' -#' @inheritParams load_austraits +#' @noRd +#' @keywords internal load_json <- function(path, update){ # Set the directory path to json @@ -113,19 +114,21 @@ load_json <- function(path, update){ #' #' @param res output of austraits.json #' @return dataframe of metadata (date of release, doi and version) +#' @noRd +#' @keywords internal create_metadata <- function(res){ # Version table - ret <- res$hits$hits$metadata |> - select(tidyselect::all_of(c("publication_date", "doi", "version"))) |> - dplyr::mutate(version = gsub("v", "", version) |> numeric_version(), + ret <- res$hits$hits$metadata %>% + dplyr::select(tidyselect::all_of(c("publication_date", "doi", "version"))) %>% + dplyr::mutate(version = gsub("v", "", version) %>% numeric_version(), id = stringr::str_remove_all(doi, stringr::fixed("10.5281/zenodo.")) - )|> # set as numeric version for easier filtering - dplyr::filter(version >= "3.0.2") |> # exclude everything pre 3.0.2 + )%>% # set as numeric version for easier filtering + dplyr::filter(version >= "3.0.2") %>% # exclude everything pre 3.0.2 dplyr::mutate(version = as.character(version), - publication_date = lubridate::ymd(publication_date)) |> # change back as character - dplyr::tibble() |> - arrange(dplyr::desc(publication_date)) + publication_date = lubridate::ymd(publication_date)) %>% # change back as character + dplyr::tibble() %>% + dplyr::arrange(dplyr::desc(publication_date)) ret } @@ -135,6 +138,8 @@ create_metadata <- function(res){ #' @param url url of download via Zenodo API #' @param filename Name of file that will be downloaded e.g. austraits-3.0.2.rds #' @param path file path to where AusTraits will be downloaded +#' @noRd +#' @keywords internal download_austraits <- function(url, filename, path) { # Get user timeout option @@ -223,10 +228,10 @@ get_version_latest <- function(path = "data/austraits", update = TRUE){ metadata <- create_metadata(res) # Sort old to new - metadata <- metadata |> + metadata <- metadata %>% dplyr::arrange(dplyr::desc(publication_date)) # Grab the first version - dplyr::first(metadata$version) |> as.character() + dplyr::first(metadata$version) %>% as.character() } diff --git a/R/lookup.R b/R/lookup.R deleted file mode 100644 index b1c864e..0000000 --- a/R/lookup.R +++ /dev/null @@ -1,24 +0,0 @@ -#' Look up a particular trait term -#' -#' @param austraits austraits list -#' @param term character string for trait search term -#' -#' @return vector containing traits that contains search term -#' @export -#' -#' @examples -#' \dontrun{ -#' austraits %>% lookup_trait("leaf") %>% extract_trait(austraits, .) -#' } -lookup_trait <- function(austraits, term){ - - all_traits <- austraits$traits$trait_name %>% unique() - - ret <- stringr::str_subset(all_traits, term) - - if(length(ret) == 0){ - stop(paste0("No traits found containing ", term, " !")) - } - - ret -} diff --git a/R/lookup_.R b/R/lookup_.R new file mode 100644 index 0000000..3c0c1e6 --- /dev/null +++ b/R/lookup_.R @@ -0,0 +1,84 @@ +#' Look up a particular trait term +#' +#' @param database traits.build database (list object) +#' @param term character string for trait search term +#' +#' @return vector containing traits that contains search term +#' @export +#' +#' @examples +#' \dontrun{ +#' austraits %>% lookup_trait("leaf") %>% extract_trait(database = austraits, .) +#' } +lookup_trait <- function(database, term){ + + all_traits <- database$traits$trait_name %>% unique() + + ret <- stringr::str_subset(all_traits, term) + + if(length(ret) == 0){ + stop(paste0("No traits found containing ", term, " !")) + } + + ret +} + + +#' Look up location properties +#' +#' @description +#' Look up location properties that contain a specific search term. +#' +#' +#' @param database traits.build database (list object) +#' @param term character string for location property search term +#' +#' @return vector containing location properties that contains search term +#' @export +#' +#' @examples +#' \dontrun{ +#' austraits %>% lookup_location_property("soil") +#' } +lookup_location_property <- function(database, term){ + + all_location_properties <- database$locations$location_property %>% unique() + + ret <- stringr::str_subset(all_location_properties, term) + + if(length(ret) == 0){ + stop(paste0("No location properties found containing ", term, " !")) + } + + ret +} + + +#' Look up context properties +#' +#' @description +#' Look up context properties that contain a specific search term. +#' +#' +#' @param database traits.build database (list object) +#' @param term character string for context property search term +#' +#' @return vector containing context properties that contains search term +#' @export +#' +#' @examples +#' \dontrun{ +#' austraits %>% lookup_context_property("temperature") +#' } +lookup_context_property <- function(database, term){ + + all_context_properties <- database$contexts$context_property %>% unique() + + ret <- stringr::str_subset(all_context_properties, term) + + if(length(ret) == 0){ + stop(paste0("No context properties found containing ", term, " !")) + } + + ret +} diff --git a/R/plot_locations.R b/R/plot_locations.R index 83f6df4..0f69930 100644 --- a/R/plot_locations.R +++ b/R/plot_locations.R @@ -1,6 +1,6 @@ #' @title Produce location maps of trait values #' @description Plot location where trait data was collected from -#' @param aus_traits austraits object OR traits table. Note location details must be joined. See join_all and examples +#' @param database traits.build database OR traits table from a traits.build database. Note location details must be joined. See join_location_coordinates and examples #' @param feature grouping/classification categories e.g trait_name, collection_type for <= v3.0.2, basis of record for >3.0.2 #' @param ... arguments passed to ggplot() #' @author Dony Indiarto - d.indiarto@student.unsw.edu.au @@ -8,105 +8,52 @@ #' @examples #' \dontrun{ #' #All traits from a given study -#' data <- austraits %>% extract_dataset(dataset_id = "Falster_2003") %>% join_all() +#' data <- austraits %>% extract_dataset(dataset_id = "Falster_2003") %>% join_location_coordinates() #' data %>% plot_locations("trait_name") #' #' #Single trait -#' data <- austraits %>% extract_trait(trait_names = c("plant_height")) %>% join_all() +#' data <- austraits %>% extract_trait(trait_names = c("plant_height")) %>% join_location_coordinates() #' data$traits %>% plot_locations("trait_name") #' } #' @export -plot_locations <- function(aus_traits, feature="trait_name", ...){ - # Setting up - ## Determine version using col names of traits table - if(any(stringr::str_detect(names(aus_traits), "location"))){ - version = "newer" - } else( - version = "older" - ) - - switch (version, - 'newer' = plot_locations2(aus_traits, feature), - 'older' = plot_locations1(aus_traits, feature) - ) -} - -#' Location plot for AusTraits versions <= 3.0.2 -#' @noRd -plot_locations1 <- function(aus_traits, feature, ...){ - au_map <- australia_map_raster %>% - dplyr::mutate(australia = as.factor(australia)) +plot_locations <- function(database, feature="trait_name", ...){ - if( is.null(dim(aus_traits)) ){ - traits <- aus_traits$traits - } else{ - traits <- aus_traits + # Check if traits.build object or the traits table + # If traits.build, check if traits table contains coordinate cols + if( is.null(dim(database)) ){ + + # Extract traits table if needed + traits <- get_traits_table(database) + + if( length(stringr::str_which(names(traits), "(deg)")) < 2 ){ + cli::cli_alert_info("Coordinate columns were not detected, joining location tables now.") + database <- database %>% join_location_coordinates() + traits <- get_traits_table(database) + } + } else { + traits <- database #If not traits.build, assign traits table as traits + + # Check if traits contains coordinate cols in traits table + if( length(stringr::str_which(names(traits), "(deg)")) < 2 ) + cli::cli_abort("No location data found in traits table - try `join_location_coordinates()` first before `plot_locations()`") } - #Create site data - sites <- - traits %>% - dplyr::select(site_name, `latitude (deg)`, `longitude (deg)`, !!feature) %>% - tidyr::drop_na() %>% - dplyr::mutate(dplyr::across(c("longitude (deg)","latitude (deg)"), as.numeric)) %>% - dplyr::filter( - `latitude (deg)` > (-45), `latitude (deg)` < (-9.5), - `longitude (deg)` > (110), `longitude (deg)` < (153)) - - #Create site map - site_map <- - ggplot2::ggplot() + - ggplot2::geom_raster(data = au_map, ggplot2::aes(x = x, y = y, fill = australia), show.legend = FALSE) + - # Add trait data - ggpointdensity::geom_pointdensity( - data = sites, - ggplot2::aes(y = `latitude (deg)`, x = `longitude (deg)`), - inherit.aes = FALSE, - show.legend = TRUE, - adjust = 1, - ... - ) + - ggplot2::scale_x_continuous(limits = c(NA, 154)) + - ggplot2::scale_fill_manual(values = "cadetblue4", na.value="white", guide = "none") + - viridis::scale_color_viridis(option = "plasma") + - ggplot2::theme( - legend.justification = c(-0.1, 0), - legend.position = "bottom", - legend.direction = "horizontal", - panel.grid.major = ggplot2::element_blank(), - panel.grid.minor = ggplot2::element_blank(), - panel.background = ggplot2::element_blank(), - panel.border = ggplot2::element_rect(colour = "black", fill=NA, linewidth=1), - axis.ticks.length = ggplot2::unit(1, "mm"), - axis.ticks = ggplot2::element_line(linewidth = 1) - ) + ggplot2::xlab("") + ggplot2::ylab("") + - ggplot2::coord_fixed() - # facet by feature if specified - default - if(!is.na(feature)){ - site_map <- site_map + ggplot2::facet_wrap(paste("~", feature)) - } - suppressWarnings(print(site_map)) + plot_locations2(traits, feature) } #' Location plot for AusTraits versions > 3.0.2 #' @noRd -plot_locations2 <- function(aus_traits, feature, ...){ +plot_locations2 <- function(database, feature, ...){ au_map <- australia_map_raster %>% dplyr::mutate(australia = as.factor(australia)) - if( is.null(dim(aus_traits)) ){ - traits <- aus_traits$traits - } else{ - traits <- aus_traits - } - #Create site data - sites <- - traits %>% - dplyr::select(location_name, `latitude (deg)`, `longitude (deg)`, !!feature) %>% - tidyr::drop_na() %>% + sites <- + database %>% + dplyr::select(!!feature, tidyselect::any_of(c("site_name", "location_name", "latitude (deg)", "longitude (deg)"))) %>% + tidyr::drop_na() %>% dplyr::mutate(dplyr::across(c("longitude (deg)","latitude (deg)"), as.numeric)) %>% dplyr::filter( `latitude (deg)` > (-45), `latitude (deg)` < (-9.5), @@ -154,15 +101,27 @@ plot_locations2 <- function(aus_traits, feature, ...){ #' @description `r lifecycle::badge('deprecated')` #' #'Plot location where trait data was collected from -#' @param traits traits table with site details appended. See join_all and examples +#' @param trait_data traits table in a traits.build database with site details appended. See join_location_coordinates and examples #' @param feature grouping/classification categories e.g trait_name, collection_type for <= v3.0.2 #' @param ... arguments passed to ggplot() #' @author Dony Indiarto - d.indiarto@student.unsw.edu.au #' @return ggplot of sites #' @export -plot_site_locations <- function(traits, feature="trait_name", ...){ - .Deprecated("plot_locations") +plot_site_locations <- function(trait_data, feature="trait_name", ...){ + # Extract function name + function_name <- as.character(sys.calls()[[1]])[1] - plot_locations1(traits, feature="trait_name", ...) + # Determine if traits table or traits.build object + if( is.null(dim(trait_data))){ + # Extract AusTraits version + AusTraits_version <- print_version(database) + } else + AusTraits_version <- "< 5.0.0" + + cli::cli_abort(c( + "i" = "{function_name} has been deprecated!", + ">" = "Use plot_locations() instead" + ) + ) } diff --git a/R/plot_trait_distribution_beeswarm.R b/R/plot_trait_distribution_beeswarm.R index 8db9722..4e5c75e 100644 --- a/R/plot_trait_distribution_beeswarm.R +++ b/R/plot_trait_distribution_beeswarm.R @@ -1,11 +1,11 @@ #' @title Beeswarm Trait distribution #' @description Plots distribution of trait values by a grouping variable using ggbeeswarm package #' -#' @param austraits austraits data object -#' @param plant_trait_name Name of trait to plot +#' @param database traits.build database (list object) +#' @param trait_name Name of trait to plot #' @param y_axis_category One of `dataset_id`, `family` -#' @param highlight specify a group to highlight -#' @param hide_ids add label on y_axis? +#' @param highlight Specify a group to highlight +#' @param hide_ids Logical for whether to add a label on y_axis? #' #' @export #' @@ -17,14 +17,23 @@ #' @export # -plot_trait_distribution_beeswarm <- function(austraits, plant_trait_name, y_axis_category, highlight=NA, hide_ids = FALSE) { - # Determine version - version <- austraits$build_info$version %>% as.character() - +plot_trait_distribution_beeswarm <- function(database, + trait_name, + y_axis_category, + highlight = NA, + hide_ids = FALSE) { + + # Check compatability + status <- check_compatibility(database, single_table_allowed = TRUE) + + # If compatible + if(!status) { + function_not_supported(database) + } # Subset data to this trait - austraits_trait <- extract_trait(austraits, plant_trait_name) + database_trait <- extract_trait(database, trait_name) - my_shapes = c("_min" = 60, "_mean" = 16, "_max" =62, "unknown" = 18) + my_shapes <- c("_min" = 60, "_mean" = 16, "_max" = 62, "unknown" = 18) as_shape <- function(value_type) { p <- rep("unknown", length(value_type)) @@ -35,21 +44,33 @@ plot_trait_distribution_beeswarm <- function(austraits, plant_trait_name, y_axis factor(p, levels=names(my_shapes)) } - tax_info <- austraits_trait$taxa %>% dplyr::select(taxon_name, family) + if (is.null(dim(database_trait))) { + + tax_info <- database_trait$taxa %>% dplyr::select(taxon_name, family, genus) + + data <- + database_trait$traits %>% + dplyr::left_join(by = "taxon_name", tax_info) + + } else { + + data <- database_trait - data <- - austraits_trait$traits %>% + } + + data <- data %>% dplyr::mutate(shapes = as_shape(value_type)) %>% - dplyr::left_join(by = "taxon_name", tax_info) + dplyr::mutate(value = as.numeric(value)) # Define grouping variables and derivatives - if(!y_axis_category %in% names(data)){ - stop("Incorrect grouping variable! Currently implemented for `family` or `dataset_id`") + if(!y_axis_category %in% names(data)) { + stop("Incorrect grouping variable! Grouping variable must be a variable in or joined to the traits table. Family and genus are supported if your input is a complete traits.build database.") } # define grouping variable, ordered by group-level by mean values # use log_value where possible - if(min(data$value, na.rm=TRUE) > 0 ) { + + if(min(data$value, na.rm=TRUE) > 0) { data$value2 <- log10(data$value) } else { data$value2 <- data$value @@ -66,15 +87,16 @@ plot_trait_distribution_beeswarm <- function(austraits, plant_trait_name, y_axis if(!is.na(highlight) & highlight %in% data$Group) { data <- dplyr::mutate(data, colour = ifelse(Group %in% highlight, "c", colour)) } + + if (is.null(dim(database))) { - # Check range on x-axis - if(package_version(version) <= '3.0.2'){ - vals <- austraits_trait$definitions$traits$elements[[plant_trait_name]]$value - } + vals <- list(minimum = purrr::pluck(database_trait, "definitions", trait_name, "allowed_values_min"), + maximum = purrr::pluck(database_trait, "definitions", trait_name, "allowed_values_max")) - if(package_version(version) > '3.0.2'){ - vals <- list(minimum = purrr::pluck(austraits_trait, "definitions", plant_trait_name, "allowed_values_min"), - maximum = purrr::pluck(austraits_trait, "definitions", plant_trait_name, "allowed_values_max")) + } else { + + vals <- list(minimum = 0.8*min(data$value), + maximum = 1.2*max(data$value)) } range <- (vals$maximum/vals$minimum) @@ -100,7 +122,7 @@ plot_trait_distribution_beeswarm <- function(austraits, plant_trait_name, y_axis # Second plot -- dots by groups, using ggbeeswarm package p2 <- ggplot2::ggplot(data, ggplot2::aes(x = value, y = Group, colour = colour, shape = shapes)) + - ggbeeswarm::geom_quasirandom() + + ggbeeswarm::geom_quasirandom(orientation = 'x') + ggplot2::ylab(paste("By ", y_axis_category)) + # inclusion of custom shapes: for min, mean, unknown # NB: this single line of code makes function about 4-5 slower for some reason @@ -140,14 +162,14 @@ plot_trait_distribution_beeswarm <- function(austraits, plant_trait_name, y_axis labels = scientific_10, limits=c(vals$minimum, vals$maximum)) p2 <- p2 + - ggplot2::scale_x_log10(name=paste(plant_trait_name, ' (', data$unit[1], ')'), + ggplot2::scale_x_log10(name=paste(trait_name, ' (', data$unit[1], ')'), breaks = scales::breaks_log(), labels = scientific_10, limits=c(vals$minimum, vals$maximum)) } else { p1 <- p1 + ggplot2::scale_x_continuous(limits=c(vals$minimum, vals$maximum)) p2 <- p2 + ggplot2::scale_x_continuous(limits=c(vals$minimum, vals$maximum)) + - ggplot2::xlab(paste(plant_trait_name, ' (', data$unit[1], ')')) + ggplot2::xlab(paste(trait_name, ' (', data$unit[1], ')')) } diff --git a/R/print.austraits.R b/R/print.austraits.R deleted file mode 100644 index 2a83330..0000000 --- a/R/print.austraits.R +++ /dev/null @@ -1,49 +0,0 @@ -#' @title Generic for outputting a nice summary for austraits objects -#' -#' @name print.austraits -#' @param x austraits list object -#' @param \dots passed to print -#' -#' @return nicely printed table -#' @export - -print.austraits <- function(x, ...){ - - # Setting up - version <- x$build_info$version %>% as.character() - nrecords <- nrow(x$traits) - nspecies <- unique(x$traits$taxon_name) %>% length() - ntraits <- unique(x$traits$trait_name) %>% length() - - cat("This is version", - version, - "of austraits!\n", - "\nThis object contains a total of", - nrecords, "records", - "for", nspecies, "taxa and", - ntraits, "traits.\n") - - if(package_version(version) <= '3.0.2'){ - - cat("\nThis object is a 'list' with the following components:\n\n", - x$definitions$austraits$elements %>% - purrr::map(~.x[["description"]]) %>% - as.vector() %>% - sprintf("- `%s`: %s", names(.), .) %>% - paste(collapse="\n") - ) - } else{ - cat("\nThis object is a 'list' with the following components:\n\n", - x$schema$austraits$elements %>% - purrr::map(~.x[["description"]]) %>% - as.vector() %>% - sprintf("- `%s`: %s", names(.), .) %>% - paste(collapse="\n") - ) - } - - - cat("\n\nTo access a component, try using the $ e.g. austraits$traits") -} - - diff --git a/R/print.traits.build.R b/R/print.traits.build.R new file mode 100644 index 0000000..cc6d49f --- /dev/null +++ b/R/print.traits.build.R @@ -0,0 +1,88 @@ +#' @title Generic for outputting a nice summary for austraits objects +#' +#' @name print.traits.build +#' @param x traits.build database +#' @param \dots passed to print +#' +#' @return nicely printed table +#' @export + +print.traits.build <- function(x, ...){ + + # Setting up printing information + version <- x$build_info$version %>% as.character() + nrecords <- nrow(x$traits) + nspecies <- unique(x$traits$taxon_name) %>% length() + ntraits <- unique(x$traits$trait_name) %>% length() + + + if(check_compatibility(x)){ + database_name <- x$metadata$title + + traits.build_version <- x$metadata$related_identifiers |> + convert_list_to_df2() |> + dplyr::filter(resource_type == "software") |> + dplyr::pull(version) + + nice_summary_output <- function() { + cli::cli_h1("This is {version} of {database_name}!") + + cli::cli_bullets(c( + "i" = "This database is built using traits.build version {traits.build_version}", + "i" = "This database contains a total of {nrecords} records, for {nspecies} taxa and {ntraits} traits." + ) + ) + + cli::cli_h2("This object is a 'list' with the following components:") + cli::cli_div(theme = list(span.emph = list(color = "forestgreen"))) + cli::cli_ul() + cli::cli_li("{.emph traits}: A table containing measurements of traits.") + cli::cli_li("{.emph locations}: A table containing observations of location/site characteristics associated with information in `traits`. Cross referencing between the two dataframes is possible using combinations of the variables `dataset_id`, `location_name`.") + cli::cli_li("{.emph contexts}: A table containing observations of contextual characteristics associated with information in `traits`. Cross referencing between the two dataframes is possible using combinations of the variables `dataset_id`, `link_id`, and `link_vals`.") + cli::cli_li("{.emph methods}: A table containing details on methods with which data were collected, including time frame and source. Cross referencing with the `traits` table is possible using combinations of the variables `dataset_id`, `trait_name`.") + cli::cli_li("{.emph excluded_data}: A table of data that did not pass quality test and so were excluded from the master dataset.") + cli::cli_li("{.emph taxonomic_updates}: A table of all taxonomic changes implemented in the construction of AusTraits. Changes are determined by comapring against the APC (Australian Plant Census) and APNI (Australian Plant Names Index).") + cli::cli_li("{.emph taxa}: A table containing details on taxa associated with information in `traits`. This information has been sourced from the APC (Australian Plant Census) and APNI (Australian Plant Names Index) and is released under a CC-BY3 license.") + cli::cli_li("{.emph contributors}: A table of people contributing to each study.") + cli::cli_li("{.emph sources}: Bibtex entries for all primary and secondary sources in the compilation.") + cli::cli_li("{.emph definitions}: A copy of the definitions for all tables and terms. Information included here was used to process data and generate any documentation for the study.") + cli::cli_li("{.emph schema}: A copy of the schema for all tables and terms. Information included here was used to process data and generate any documentation for the study.") + cli::cli_li("{.emph metadata}: Metadata associated with the dataset, including title, creators, license, subject, funding sources.") + cli::cli_li("{.emph build_info}: A description of the computing environment used to create this version of the dataset, including version number, git commit and R session_info.") + cli::cli_end() + + cli::cli_alert_info("To access a component, try using the $ e.g. austraits$traits") + } + + nice_summary_output() + } else { # If not compatible (i.e. old version of database) + # Setting up + database_name <- x$definitions$austraits$description + + old_version_nice_output <- function() { + cli::cli_h1("This database contains a total of {nrecords} records, for {nspecies} taxa and {ntraits} traits.") + + cli::cli_h2("This object is a 'list' with the following components:") + cli::cli_div(theme = list(span.emph = list(color = "forestgreen"))) + cli::cli_ul() + cli::cli_li("{.emph traits}: A table containing measurements of traits.") + cli::cli_li("{.emph locations}: A table containing observations of location/site characteristics associated with information in `traits`. Cross referencing between the two dataframes is possible using combinations of the variables `dataset_id`, `location_name`.") + cli::cli_li("{.emph contexts}: A table containing observations of contextual characteristics associated with information in `traits`. Cross referencing between the two dataframes is possible using combinations of the variables `dataset_id`, `link_id`, and `link_vals`.") + cli::cli_li("{.emph methods}: A table containing details on methods with which data were collected, including time frame and source. Cross referencing with the `traits` table is possible using combinations of the variables `dataset_id`, `trait_name`.") + cli::cli_li("{.emph excluded_data}: A table of data that did not pass quality test and so were excluded from the master dataset.") + cli::cli_li("{.emph taxonomic_updates}: A table of all taxonomic changes implemented in the construction of AusTraits. Changes are determined by comapring against the APC (Australian Plant Census) and APNI (Australian Plant Names Index).") + cli::cli_li("{.emph taxa}: A table containing details on taxa associated with information in `traits`. This information has been sourced from the APC (Australian Plant Census) and APNI (Australian Plant Names Index) and is released under a CC-BY3 license.") + cli::cli_li("{.emph definitions}: A copy of the definitions for all tables and terms. Information included here was used to process data and generate any documentation for the study.") + cli::cli_li("{.emph contributors}: A table of people contributing to each study.") + cli::cli_li("{.emph sources}: Bibtex entries for all primary and secondary sources in the compilation.") + cli::cli_li("{.emph build_info}: A description of the computing environment used to create this version of the dataset, including version number, git commit and R session_info.") + cli::cli_end() + + cli::cli_alert_info("To access a component, try using the $ e.g. austraits$traits") + } + + old_version_nice_output() + } +} + + diff --git a/R/separate_trait_values.R b/R/separate_trait_values.R new file mode 100644 index 0000000..4886f1c --- /dev/null +++ b/R/separate_trait_values.R @@ -0,0 +1,60 @@ +#' @title Separate bounded trait values +#' +#' @description This function reverts the action of bind_trait_values. +#' This function separates values that were concatenated so that studies that have multiple observations for a given trait will have seperate row for each observation. +#' @usage separate_trait_values(trait_data, definitions) +#' @param trait_data The traits table in a traits.build database - see example +#' @param definitions The austraits definitions data frame +#' @return trait tibble +#' @examples +#' \dontrun{ +#' trait_data <- austraits$traits %>% +#' dplyr::filter(dataset_id == "Falster_2005_1") +#' trait_data +#' traits_bind <- bind_trait_values(trait_data) +#' separate_trait_values(traits_bind) +#' } +#' @author Daniel Falster - daniel.falster@unsw.edu.au +#' @export + +#' +separate_trait_values <- function(trait_data, definitions) { + + separate_x <- function(x) strsplit(x, "--")[[1]] + + separate_values_worker <- function(df) { + + df[rep(1, df$n_vals[1]),] %>% + dplyr::mutate( + value = separate_x(value[1]), + value_type = separate_x(value_type[1]), + basis_of_value = separate_x(basis_of_value[1]), + replicates = separate_x(replicates[1]) + ) + } + + # record the number of values in each row of data + trait_data$n_vals <- 1 + stringr::str_count(trait_data$value_type, "--") + + # separate out those rows requiring no modification + out_1 <- trait_data %>% + dplyr::filter(n_vals == 1) + + if (nrow(dplyr::filter(trait_data, n_vals > 1)) > 0) { + # separate out those rows requiring modification & modify + out_2 <- trait_data %>% + dplyr::filter(n_vals > 1) %>% + dplyr::group_split(stringr::str_c(dataset_id, observation_id, trait_name, method_id, method_context_id, repeat_measurements_id, sep = " ")) %>% + lapply(separate_values_worker) %>% + dplyr::bind_rows() %>% + dplyr::select(dataset_id:n_vals) + + # join it all back together, clean up and sort as in original + dplyr::bind_rows(out_1, out_2) %>% + dplyr::select(-n_vals) %>% + dplyr::mutate(replicates = clean_NA(replicates), + value_type = factor(clean_NA(value_type), levels = names(definitions$definitions$value_type$values)) + ) %>% + dplyr::arrange(observation_id, trait_name, value_type) + } +} diff --git a/R/seperate_trait_values.R b/R/seperate_trait_values.R deleted file mode 100644 index e4d731b..0000000 --- a/R/seperate_trait_values.R +++ /dev/null @@ -1,57 +0,0 @@ -#' @title Separate bounded trait values -#' -#' @description This function reverts the action of bind_trait_values. -#' This function separates values that were concatenated so that studies that have multiple observations for a given trait will have seperate row for each observation. -#' @usage separate_trait_values(data, definitions) -#' @param data The trait data frame generated from austraits - see example -#' @param definitions The austraits definitions data frame -#' @return trait tibble -#' @examples -#' \dontrun{ -#' traits <- austraits$traits %>% -#' dplyr::filter(dataset_id == "Falster_2005_1") -#' traits -#' traits_bind <- bind_trait_values(traits) -#' separate_trait_values(traits_bind) -#' } -#' @author Daniel Falster - daniel.falster@unsw.edu.au -#' @export - -#' -separate_trait_values <- function(data, definitions) { - - separate_x <- function(x) strsplit(x, "--")[[1]] - - separate_values_worker <- function(df) { - - df[rep(1, df$n_vals[1]),] %>% - dplyr::mutate( - value = separate_x(value[1]), - value_type = separate_x(value_type[1]), - replicates = separate_x(replicates[1]) - ) - } - - # record the number of values in each row of data - data$n_vals <- 1 + stringr::str_count(data$value_type, "--") - - # separate out those rows requiring no modification - out_1 <- data %>% - dplyr::filter(n_vals == 1) - - # separate out those rows requiring modification & modify - out_2 <- data %>% - dplyr::filter(n_vals > 1) %>% - dplyr::group_split(stringr::str_c(observation_id, trait_name, sep = " ")) %>% - lapply(separate_values_worker) %>% - dplyr::bind_rows() %>% - dplyr::select(dataset_id:n_vals) - - # join it all back together, clean up and sort as in original - dplyr::bind_rows(out_1, out_2) %>% - dplyr::select(-n_vals) %>% - dplyr::mutate(replicates = clean_NA(replicates), - value_type = factor(clean_NA(value_type), levels = names(definitions$definitions$value_type$values)) - ) %>% - dplyr::arrange(observation_id, trait_name, value_type) -} diff --git a/R/summarise_austraits.R b/R/summarise_austraits.R index 24d7f55..85b6da8 100644 --- a/R/summarise_austraits.R +++ b/R/summarise_austraits.R @@ -1,38 +1,38 @@ #' @title Summarise counts for a particular variable of interest #' -#' @name summarise_austraits -#' @param austraits A large list of tibbles built from austraits +#' @name summarise_database +#' @param database traits.build database (list object) #' @param var variable you use wish to see summary of (trait_name, genus, family) #' #' @return dataframe of unique levels of variable with counts and percentage #' @export #' @examples #' \dontrun{ -#' summarise_austraits(austraits, "trait_name") -#' summarise_austraits(austraits, "family") +#' summarise_database(database = austraits, "trait_name") +#' summarise_database(database = austraits, "family") #' } -summarise_austraits <- function(austraits, var){ +summarise_database <- function(database, var){ if(!var %in% c("trait_name", "family", "genus")){ stop(paste0("Print summary for ", var, " has not been implemented! see examples)")) } switch(var, - trait_name = summarise_austraits_traits(austraits, var), - genus = summarise_austraits_taxa(austraits, var), - family = summarise_austraits_taxa(austraits, var) + trait_name = summarise_database_traits(database, var), + genus = summarise_database_taxa(database, var), + family = summarise_database_taxa(database, var) ) } #' @noRd #' @keywords internal -summarise_austraits_traits <-function(austraits, var) { +summarise_database_traits <-function(database, var) { ret <- - austraits[["traits"]] %>% + database[["traits"]] %>% dplyr::pull({{var}}) %>% sort() %>% janitor::tabyl() @@ -46,7 +46,7 @@ summarise_austraits_traits <-function(austraits, var) { percent_total = signif(percent, 3), percent = NULL) # Summary statistics - sum_stats <- austraits[["traits"]] %>% + sum_stats <- database[["traits"]] %>% dplyr::group_by(trait_name) %>% dplyr::summarise(n_dataset = length(unique(dataset_id)), n_taxa = length(unique(taxon_name))) @@ -54,19 +54,19 @@ summarise_austraits_traits <-function(austraits, var) { ret <- dplyr::left_join(ret, sum_stats, by = "trait_name") # Organise - ret %>% dplyr::select(1, dplyr::starts_with("n_"), percent_total) + ret %>% dplyr::select(1, dplyr::starts_with("n_"), percent_total) %>% tibble::tibble() } #' @noRd #' @keywords internal -summarise_austraits_taxa <-function(austraits, var) { +summarise_database_taxa <-function(database, var) { #Join taxonomic info - austraits <- austraits %>% join_taxonomy() + database <- database %>% join_taxa() # Create table - ret <- austraits[["traits"]] %>% + ret <- database[["traits"]] %>% dplyr::pull(var) %>% sort() %>% janitor::tabyl() @@ -84,7 +84,7 @@ summarise_austraits_taxa <-function(austraits, var) { # Summary statistics (https://stackoverflow.com/questions/55425976/use-quoted-variable-in-group-by-mutate-function-call) - sum_stats <- austraits[["traits"]] %>% + sum_stats <- database[["traits"]] %>% dplyr::group_by(!!rlang::sym(var)) %>% dplyr::summarise(n_dataset = length(unique(dataset_id)), n_taxa = length(unique(taxon_name))) @@ -92,6 +92,6 @@ summarise_austraits_taxa <-function(austraits, var) { ret <- dplyr::left_join(ret, sum_stats, by = var) # Organise - ret %>% dplyr::select(1, dplyr::starts_with("n_"), percent_total) + ret %>% dplyr::select(1, dplyr::starts_with("n_"), percent_total) %>% tibble::tibble() } diff --git a/R/summarise_trait_values.R b/R/summarise_trait_values.R deleted file mode 100644 index 2b6b2de..0000000 --- a/R/summarise_trait_values.R +++ /dev/null @@ -1,61 +0,0 @@ -#' Compute mean trait values for studies that have multiple observations for a given trait -#' -#' @param trait_data trait table for austraits list -#' -#' @return A reduced trait table, mean values are flagged with the suffix '_summarised' in value_type -#' @export -#' -#' @examples -#' \dontrun{ -#' data <- austraits$traits %>% filter(dataset_id == "Falster_2003") -#' data %>% summarise_trait_means() -#' } - - -summarise_trait_means <- function(trait_data){ - suppressWarnings( - trait_data %>% - dplyr::mutate(value = as.numeric(.data$value), - replicates = as.numeric(.data$replicates)) -> trait_data - ) - - # Identify which ones need summarising - target <- trait_data %>% - dplyr::group_by(trait_name, observation_id) %>% - dplyr::summarise(dplyr::n()) %>% - dplyr::filter(`dplyr::n()` > 1) %>% - dplyr::select("trait_name", observation_id) - - # # Identify which ones that don't need to change - original <- trait_data %>% - dplyr::group_by(trait_name, observation_id) %>% - dplyr::summarise(dplyr::n()) %>% - dplyr::filter(! `dplyr::n()` > 1) %>% - dplyr::select("trait_name", "observation_id") - - original_df <- purrr::map2_dfr(original$trait_name, original$observation_id, - ~ dplyr::filter(trait_data, trait_name == .x & observation_id == .y)) - - # Filter out the ones where nrows is > 1 - target_ls <- purrr::map2(target$trait_name, target$observation_id, - ~ dplyr::filter(trait_data, trait_name == .x & observation_id == .y) - ) - - # Manipulate: Compute means, update value type and replicates - target_summarised <- purrr::map(target_ls, - ~ .x %>% dplyr::mutate(value = mean(value, na.rm = TRUE), - value_type = paste0(value_type, "_summarised"), - replicates = sum(replicates)) %>% - dplyr::filter(dplyr::row_number() == 1) - - ) - - - target_bound <- target_summarised %>% dplyr::bind_rows() - - # Append back to the ones where nrows = 1 - ret <- dplyr::bind_rows(original_df, target_bound) - - # Sort by observation_id and return - ret %>% dplyr::arrange(.data$observation_id) -} \ No newline at end of file diff --git a/R/sysdata.rda b/R/sysdata.rda index 7fa845b..ff99683 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/R/trait_pivot_longer.R b/R/trait_pivot_longer.R index 582dbca..9c6fe67 100644 --- a/R/trait_pivot_longer.R +++ b/R/trait_pivot_longer.R @@ -1,16 +1,33 @@ -#' @title Pivot wide format AusTrait data into a long format +#' @title Pivot wide format traits table into long format #' -#' @description trait_pivot_longer "gathers" wide format data into a "tidy" format +#' @description `r lifecycle::badge('deprecated')` +#' trait_pivot_longer "gathers" wide format data into a "tidy" format #' This function converts the data into long format where observations are on different rows and the type of observation is denoted by trait name. #' In other words, trait_pivot_longer reverts the actions of trait_pivot_wider #' @param wide_data output from trait_pivot_wider. For <= v3.0.2 list object containing wide data generated,For > v3.0.2 a tibble of wide data #' @return A tibble in long format #' @details -#' - If `bind_trait_values` or `summarise_trait_means` was applied prior to `trait_pivot_wider` for AusTraits +#' - If `bind_trait_values` was applied prior to `trait_pivot_wider` for AusTraits #' <= v3.0.2, `trait_pivot_longer` will return a tibble with fewer observations than the original traits table. #' - For AusTraits version >3.0.2, `trait_pivot_longer` will return a tibble with fewer columns than that original traits table #' - The excluded columns include: "unit", "replicates", "measurement_remarks", "basis_of_record", "basis_of_value" #' +#' This function reverts the actions of the function austraits::trait_pivot_wider. +#' +#' It begins with a derivation of a traits.build traits table, where multiple measurements that comprise a single observation are displayed on a single row,with a column for each trait. It then converts the table into long format where measurements of multiple traits that comprise a single observation are on different rows and a column specifying the trait names is added. +#' +#' @param wide_data output from trait_pivot_wider. +#' @return A tibble in long format +#' @details +#' `trait_pivot_longer` has been developed to pivot the traits table for a database build using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' #' @examples #' \dontrun{ #' data <- austraits$traits %>% @@ -27,73 +44,5 @@ # trait_pivot_longer <- function(wide_data){ - # Determine version using col names of traits table - if(any(names(wide_data) %in% "treatment_context_id")){ - version = "5-series" - } - - if(any(str_detect(names(wide_data), "entity")) & any(names(wide_data) %in% "treatment_id")){ - version = "4-series" - } - - if(! any(str_detect(names(wide_data), "entity"))) - version = "3-series-earlier" - - # Switch how traits are pivoted wider based on version - switch (version, - "5-series" = trait_pivot_longer3(wide_data), - "4-series" = trait_pivot_longer2(wide_data), - "3-series-earlier" = trait_pivot_longer1(wide_data)) - -} - -#' Gathers 'widened' data for >= v5.0.0 -#' @noRd -#' @keywords internal -trait_pivot_longer3 <- function(wide_data) { - wide_data %>% - tidyr::pivot_longer(cols = 20:ncol(.), names_to = "trait_name", values_drop_na = TRUE) -} - -#' Gathers 'widened' data for > v3.0.2 < 5.0.0 -#' @noRd -#' @keywords internal -trait_pivot_longer2 <- function(wide_data) { - wide_data %>% - tidyr::pivot_longer(cols = 18:ncol(.), names_to = "trait_name", values_drop_na = TRUE) -} - -#' Gathers 'widened' data for <= v3.0.2 -#' @noRd -#' @keywords internal -trait_pivot_longer1 <- function(wide_data) { - data <- wide_data - - id_variables <- c("dataset_id", "taxon_name", "site_name", "context_name", "observation_id", "trait_name", "value", "unit", "date", "value_type", "replicates", "original_name") - - traits <- names(data$value)[!(names(data$value) %in% id_variables)] - - vars <- names(data) - - gather_f <- function(df, v) { - df[[v]] %>% tidyr::pivot_longer(cols = tidyselect::any_of(traits), names_to = "trait_name", values_to = {{v}}) - } - - ret <- gather_f(data, vars[1]) - - for(v in vars[-c(1)]) - ret <- ret %>% - dplyr::left_join( - gather_f(data, v), - by = dplyr::setdiff(id_variables, vars) - ) - - ret <- ret %>% - #dplyr::mutate(value = dplyr::na_if(value, y = "NA")) %>% - dplyr::filter(!is.na(value)) %>% - dplyr::distinct() %>% - dplyr::arrange(observation_id, trait_name) %>% - dplyr::select(tidyselect::all_of(id_variables)) - - ret + function_not_supported(wide_data) } diff --git a/R/trait_pivot_wider.R b/R/trait_pivot_wider.R index b8a92a6..b506f99 100644 --- a/R/trait_pivot_wider.R +++ b/R/trait_pivot_wider.R @@ -1,17 +1,28 @@ -#' @title Pivot long format austrait data into a wide format +#' @title Pivot long format traits table into wide format #' -#' @description `trait_pivot_wider` "widens" long format data ("tidy data") +#' @description Function to "widen" long format data ("tidy data"). #' -#' AusTraits data is organised in a long format where observations are on different rows and the type of observation is denoted by various identifying columns (e.g trait_name, dataset_id, observation_id etc.) -#' This function converts the data into wide format so that each trait in it's own column. -#' @param traits The traits table from austraits list object -#' @return list of five tibbles in wide format -#' @details -#' - For AusTraits <=v3.0.2, some studies have multiple rows of data for each observation_id, so `trait_pivot_wider` will return four lists (value, unit, value_type, date and replicates) with the identifying columns and trait data arranged in columns. -#' - For AusTraits >3.0.2, `trait_pivot_wider` will return a single widen tibble, note that some meta-data columns (unit, replicates, measurement_remarks, basis_of_record, basis_of_value) will be excluded to produce a useful wide tibble. +#' Data in a traits.build databases' traits table are organised in a long format where each trait measurement is on a different row and measurement metadata is recorded in other columns. Multiple traits may be measured as part of a single observation and this function pivots the data wider, such that each trait is its own column. Note that if two trait measurements have the same observation_id but different value types (min, mean, mode, etc.) these will be on separate rows. +#' +#' The function austraits::trait_pivot_longer reverts the actions of this function. +#' +#' @param database The traits tibble from a traits.build database +#' @return traits.build traits table in wide format +#' @details +#' `trait_pivot_wider`` has been developed to pivot the traits table for a database build using the traits.build workflow. +#' Learn more at: +#' [https://github.com/traitecoevo/traits.build](https://github.com/traitecoevo/traits.build) & +#' [https://github.com/traitecoevo/traits.build-book](https://github.com/traitecoevo/traits.build-book) +#' +#' Note to AusTraits users: +#' - This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +#' - For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see [https://github.com/traitecoevo/austraits](https://github.com/traitecoevo/austraits) for how to install old versions of the package or download a newer version of the database. +#' + #' @examples #' \dontrun{ -#' data <- austraits$traits %>% filter(dataset_id == "Falster_2003") +#' +#' data <- austraits_5.0.0_lite$traits %>% filter(dataset_id == "Falster_2003") #' data #long format #' traits_wide <- trait_pivot_wider(data) #' traits_wide #wide format @@ -19,131 +30,54 @@ #' @author Daniel Falster - daniel.falster@unsw.edu.au #' @export -trait_pivot_wider <- function(traits){ - # Determine version using col names of traits table - if(any(names(traits) %in% "treatment_context_id")){ - version = "5-series" - } - - if(any(str_detect(names(traits), "entity")) & any(names(traits) %in% "treatment_id")){ - version = "4-series" - } - - if(! any(str_detect(names(traits), "entity"))) - version = "3-series-earlier" - - # Switch how traits are pivoted wider based on version - switch (version, - "5-series" = trait_pivot_wider3(traits), - "4-series" = trait_pivot_wider2(traits), - "3-series-earlier" = trait_pivot_wider1(traits)) -} - - -#' Pivot wider for >v5.0.0 -#' @noRd -#' @keywords internal -trait_pivot_wider3 <- function(traits){ - data <- traits +trait_pivot_wider <- function(database){ + # Extract traits table if needed + traits <- get_traits_table(database) - meta_data_cols <- c("unit", "replicates", "measurement_remarks", "basis_of_value") + # Check compatibility + status <- check_traits_compatibility(traits) - # A check for if there are more than 1 value_type for a given taxon_name, observation_id and method - data %>% - select(trait_name, value, dataset_id, observation_id, method_id, method_context_id, repeat_measurements_id, value_type) %>% - group_by(dataset_id, observation_id, method_id, method_context_id, repeat_measurements_id) %>% - summarise(n_value_type = length(unique(value_type))) %>% - arrange(observation_id) %>% - dplyr::filter(n_value_type > 1) -> check_value_type - - if(nrow(check_value_type) > 1){ - - traits %>% - select(- all_of(meta_data_cols)) %>% - group_by(dataset_id, observation_id, method_id, method_context_id, repeat_measurements_id, value_type) %>% - pivot_wider(names_from = trait_name, - values_from = value) |> - dplyr::ungroup() - } else{ - - meta_data_cols <- c(meta_data_cols, "value_type") - - traits %>% - select(- all_of(meta_data_cols)) %>% - group_by(dataset_id, observation_id, method_id, method_context_id, repeat_measurements_id) %>% - pivot_wider(names_from = trait_name, - values_from = value) |> - dplyr::ungroup() + # If compatible + if(!status){ + function_not_supported(database) } -} -#' Pivot wider for >v3.0.2 & <5.0.0 -#' @noRd -#' @keywords internal -#' @importFrom dplyr select group_by arrange filter summarise -#' @importFrom tidyr pivot_wider pivot_longer -#' @importFrom tidyselect all_of -#' @importFrom stringr str_detect - -trait_pivot_wider2 <- function(traits){ - data <- traits - - meta_data_cols <- c("unit", "replicates", "measurement_remarks", "basis_of_record", "basis_of_value") + metadata_cols <- c("unit", "replicates", "measurement_remarks", "basis_of_value") # A check for if there are more than 1 value_type for a given taxon_name, observation_id and method - data %>% - dplyr::select(taxon_name, trait_name, value_type, value, observation_id, method_id) %>% - dplyr::group_by(taxon_name, observation_id, method_id) %>% - dplyr::summarise(n_value_type = length(unique(value_type))) %>% - dplyr::arrange(observation_id) %>% - dplyr::filter(n_value_type > 1) -> check_value_type - - if(nrow(check_value_type) > 1){ - - traits %>% - dplyr::select(-all_of(meta_data_cols)) %>% - dplyr::group_by(dataset_id, source_id, taxon_name, original_name, observation_id, method_id, value_type) %>% - tidyr::pivot_wider(names_from = trait_name, - values_from = value) |> - dplyr::ungroup() + check_value_type <- traits %>% + dplyr::select(dplyr::all_of(c( + "trait_name", "value", "dataset_id", "observation_id", "method_id", "method_context_id", + "repeat_measurements_id", "value_type"))) %>% + dplyr::group_by( + .data$dataset_id, .data$observation_id, .data$method_id, + .data$method_context_id, .data$repeat_measurements_id) %>% + dplyr::summarise(n_value_type = length(unique(.data$value_type))) %>% + dplyr::arrange(.data$observation_id) %>% + dplyr::filter(.data$n_value_type > 1) + + if (nrow(check_value_type) > 1) { + + traits %>% + tidyr::pivot_wider( + names_from = "trait_name", + values_from = "value", + id_cols = -dplyr::all_of(metadata_cols) + ) - } else{ + } else { - meta_data_cols <- c(meta_data_cols, "value_type") + metadata_cols <- c(metadata_cols, "value_type") - traits %>% - dplyr::select(- all_of(meta_data_cols)) %>% - dplyr::group_by(dataset_id, source_id, taxon_name, original_name, observation_id, method_id) %>% - tidyr::pivot_wider(names_from = trait_name, - values_from = value) |> - dplyr::ungroup() + traits %>% + tidyr::pivot_wider( + names_from = "trait_name", + values_from = "value", + id_cols = -dplyr::all_of(metadata_cols) + ) } } -#' Pivot wider for <=v3.0.2 -#' @noRd -#' @keywords internal -trait_pivot_wider1 <- function(traits){ - data <- traits - - check_obs <- data %>% - dplyr::group_by(trait_name, observation_id) %>% - dplyr::summarise(dplyr::n()) %>% - dplyr::filter(`dplyr::n()` > 1) %>% - dplyr::select(trait_name, observation_id) - - if(nrow(check_obs) >1){ - rlang::abort("There are multiple data points for the same observation - try summarise_trait_means() before widening!") - } - - vars <- c("value", "unit", "date", "value_type", "replicates") - - ret <- purrr::map(vars, piv_wide, data = data) - - names(ret) <- vars - - ret -} #' Helper function to pivot wider for AusTraits <= v3.0.2 #' @keywords internal diff --git a/R/utils-pipe.R b/R/utils-pipe.R deleted file mode 100644 index fd0b1d1..0000000 --- a/R/utils-pipe.R +++ /dev/null @@ -1,14 +0,0 @@ -#' Pipe operator -#' -#' See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details. -#' -#' @name %>% -#' @rdname pipe -#' @keywords internal -#' @export -#' @importFrom magrittr %>% -#' @usage lhs \%>\% rhs -#' @param lhs A value or the magrittr placeholder. -#' @param rhs A function call using the magrittr semantics. -#' @return The result of calling `rhs(lhs)`. -NULL diff --git a/R/utils.R b/R/utils.R new file mode 100644 index 0000000..508653a --- /dev/null +++ b/R/utils.R @@ -0,0 +1,143 @@ +#' Convert dataframe to list +#' +#' @description Convert a dataframe to a named list, +#' useful when converting a datafreme a to yaml. +#' +#' @param df A dataframe +#' @return A (yaml) list +#' @export +#' @examples convert_df_to_list(dplyr::starwars) +convert_df_to_list <- function(df) { + attr(df, "out.attrs") <- NULL + unname(lapply(split(df, seq_len(nrow(df))), as.list)) +} + +#' Convert list with single entries to dataframe +#' +#' @description Convert a list with a single level of entries to a dataframe, +#' useful when converting a yaml into a dataframe. +#' +#' @param my_list A list with single entries +#' @return A tibble with two columns +#' @export +#' @examples \dontrun{ +#' convert_list_to_df1(as.list(dplyr::starwars)[2]) +#' } +convert_list_to_df1 <- function(my_list) { + + for (f in names(my_list)) { + if (is.null(my_list[[f]])) + my_list[[f]] <- NA + } + + tibble::tibble(key = names(my_list), value = unname(unlist(my_list))) +} + +#' Convert list of lists to dataframe +#' +#' @description Convert a list of lists to a dataframe, +#' useful when converting a multi-level yaml into a dataframe. +#' Function required that every list have same named elements. +#' +#' @param my_list A list of lists to dataframe +#' @param as_character A logical value, indicating whether the values are read as character +#' @param on_empty Value to return if my_list is NULL, NA or is length == 0, default = NA +#' @return tibble +#' @export +#' @examples demo_list1 <- list(word1 = "this", word2 = "is", word3 = "an", word4 = "example", word5 = "list") +#' demo_list2 <- list(word1 = "and", word2 = "a", word3 = "second", word4 = "list", word5 = "also") +#' combined_list <- list(demo_list1, demo_list2) +#' convert_list_to_df2(combined_list) + +convert_list_to_df2 <- function(my_list, as_character = TRUE, on_empty = NA) { + + if (is.null(my_list) || any(is.na(my_list)) || length(my_list) == 0) + return(on_empty) + + if (as_character) + my_list <- lapply(my_list, lapply, as.character) + + dplyr::bind_rows(lapply(my_list, tibble::as_tibble)) +} + +#' Notify user the function they are using is no longer support +#' +#' @param database traits.build database (list object) +#' +#' @return cli messaging about the function name, the version of AusTraits they are using and their next options +#' @keywords internal +#' @noRd + +function_not_supported <- function(database, ...){ + + # Extract function name + function_name <- as.character(sys.calls()[[1]])[1] + + # Determine if traits table or traits.build object + if( is.null(dim(database))){ + # Extract AusTraits version + AusTraits_version <- print_version(database) + } else + AusTraits_version <- "< 5.0.0" + + # Formulate message + cli::cli_abort(c( + "x" = "{function_name} no longer supports AusTraits version {AusTraits_version}", + "i" = "You can either update to a newer version of the data using `load_austraits()` OR", + "i" = "Install an older version of the package", + "i" = "See https://github.com/traitecoevo/austraits for details." + ), + call = rlang::caller_env() + ) +} + + +#' Retrieve traits table if user passes traits.build object. +#' +#' @param database traits.build database or traits table in a traits.build database + + +get_traits_table <- function(database){ + if( is.null(dim(database)) ){ + traits <- database$traits + } else{ + traits <- database + } + + return(traits) +} + + +#' @title NA hygiene +#' +#' @description Helper function to convert character strings of NA into true NA +#' @usage clean_NA(x) +#' @param trait_data The traits table in a traits.build database +#' @param definitions The definitions tibble from a traits.build database +#' @return vector where strings of NA are treated as true NA +#' @examples +#' \dontrun{ +#' clean_NA(c("NA", 1, 2, 3))) %>% is.na() +#' } +#' @author Daniel Falster - daniel.falster@unsw.edu.au + +#' @noRd + +clean_NA <- function(x) { + ifelse(x == "NA", NA_character_, x) +} + +#' Pipe operator +#' +#' See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details. +#' +#' @name %>% +#' @rdname pipe +#' @keywords internal +#' @export +#' @importFrom magrittr %>% +#' @usage lhs \%>\% rhs +#' @param lhs A value or the magrittr placeholder. +#' @param rhs A function call using the magrittr semantics. +#' @return The result of calling `rhs(lhs)`. +NULL \ No newline at end of file diff --git a/R/what_version.R b/R/what_version.R index b620d40..9836ca7 100644 --- a/R/what_version.R +++ b/R/what_version.R @@ -1,12 +1,14 @@ -#' Determine whether version was pre or post 3.0.2 +#' Identify austraits.build or traits.build version +#' +#' @description Determine whether database version was built by austraits.build (AusTraits pre 5.0.0) or traits.build (AusTraits post 5.0.0) #' -#' @param austraits austraits list object +#' @param database traits.build database (list object) #' @return binary version for switch statements #' @noRd #' @keywords internal #' -what_version <- function(austraits){ - version <- austraits$build_info$version %>% as.character() +what_version <- function(database){ + version <- database$build_info$version %>% as.character() if(package_version(version) <= '3.0.2'){ ret_version <- "3-series-earlier" @@ -20,4 +22,15 @@ what_version <- function(austraits){ ret_version <- "5-series" } ret_version +} + +#' Print version of AusTraits object +#' +#' @param database traits.build database (list object) +#' @return binary version for switch statements +#' @noRd +#' @keywords internal +#' +print_version <- function(database){ + database$build_info$version %>% as.character() } \ No newline at end of file diff --git a/README.Rmd b/README.Rmd index 0036cc7..63e4d09 100644 --- a/README.Rmd +++ b/README.Rmd @@ -55,6 +55,25 @@ Otherwise, for a lightweight installation where dependencies for plotting and th remotes::install_github("traitecoevo/austraits", upgrade = "ask") ``` +#### Backwards compatibility with old AusTraits versions + +In September 2024 austraits functions were revamped to support all [traits.build](https://github.com/traitecoevo/traits.build) compiled databases, rather than being linked to [austraits.build](https://github.com/traitecoevo/austraits.build). + +Versions of austraits.build (the AusTraits plant trait database) < 5.0 are no longer supported by the current functions. If you are working with an older version of AusTraits, please install an older version of austraits: + +For austraits.build versions 4.2 and older: +```{r setup, results = 'hide', eval = FALSE} +#install.packages("remotes") +remotes::install_github("traitecoevo/austraits@53b637c", dependencies = TRUE, upgrade = "ask") + +library(austraits) +``` + +Note, if you are unsure what version of AusTraits you are working with, run: +```{r setup, results = 'hide', eval = FALSE} +austraits$build_info$version +``` + ### Take a good look at our vignettes! `r emo::ji("eyes")` diff --git a/_pkgdown.yml b/_pkgdown.yml index f11b161..9099e2c 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -25,7 +25,6 @@ reference: - contents: - starts_with("extract") - starts_with("trait_pivot") - - summarise_trait_means - starts_with("join") - ends_with("trait_values") - as_wide_table diff --git a/codecov.yml b/codecov.yml index 4fdf441..754616b 100644 --- a/codecov.yml +++ b/codecov.yml @@ -12,3 +12,6 @@ coverage: target: 70% threshold: 1% informational: true + +codecov: + token: 0ce67146-bca7-456f-9a08-6039b36d47f3 \ No newline at end of file diff --git a/data-raw/create_data.R b/data-raw/create_data.R index e9fe2b7..4421652 100644 --- a/data-raw/create_data.R +++ b/data-raw/create_data.R @@ -7,28 +7,36 @@ path = "ignore/data/austraits" # 3.0.2 austraits_3.0.2 <- load_austraits(version = "3.0.2", path = path) -set.seed(109) -dataset_id <- c( unique(austraits_3.0.2$traits$dataset_id) %>% sample(5), "Falster_2003", "Falster_2005_1", "Falster_2005_2" ) +austraits_3.0.2_lite <- list() -austraits_3.0.2_lite <- extract_dataset(austraits_3.0.2, dataset_id) +austraits_3.0.2_lite$traits <- austraits_3.0.2$traits %>% dplyr::filter(is.na(dataset_id)) # 4.2.0 -datasets <- c("Crous_2013", "Crous_2019", "Buckton_2019", "Kooyman_2011", "Bloomfield_2018", - "Wright_2019", "Westoby_2014", "Vesk_2019", "Leigh_2003", "Prior_2003", - "Prior_2016", "Choat_2006", "Choat_2012", "ABRS_1981") - austraits_4.2.0 <- load_austraits(version = "4.2.0", path = path) -austraits_4.2.0_lite <- austraits_4.2.0 |> extract_dataset(dataset_id = c(dataset_id, datasets)) + +austraits_4.2.0_lite <- list() +austraits_4.2.0_lite$traits <- austraits_4.2.0$traits %>% dplyr::filter(is.na(dataset_id)) +austraits_4.2.0_lite$metadata <- austraits_4.2.0$metadata # 5.0.0 austraits_5.0.0 <- load_austraits(version = "5.0.0", path = path) +set.seed(109) + +dataset_id <- c(unique(austraits_5.0.0$traits$dataset_id) %>% sample(5)) + + +datasets <- c("Falster_2003", "Falster_2005_1", "Falster_2005_2", + "", "Crous_2019", "Buckton_2019", "Kooyman_2011", "Bloomfield_2018", + "Wright_2019", "Westoby_2014", "Vesk_2019", "Leigh_2003", "Prior_2003", + "Prior_2016", "Choat_2006", "Choat_2012", "ABRS_1981", "Cernusak_2006", "Yang_2023") + austraits_5.0.0_lite <- austraits_5.0.0 %>% extract_dataset(dataset_id = c(dataset_id, datasets)) ## code to prepare `australia_map_raster` dataset -australia_map_raster <- raster::raster("ignore/australia.tif") +australia_map_raster <- raster::raster("ignore/australia.tif") australia_map_raster <- australia_map_raster %>% raster::as.data.frame(xy = T,na.rm=T) usethis::use_data(austraits_3.0.2_lite, austraits_4.2.0_lite, austraits_5.0.0_lite, australia_map_raster, internal = TRUE, overwrite = TRUE) - +#usethis::use_data(austraits_5.0.0_lite, internal = TRUE, overwrite = TRUE) diff --git a/man/as_wide_table.Rd b/man/as_wide_table.Rd index 7f8a328..8ff2ef9 100644 --- a/man/as_wide_table.Rd +++ b/man/as_wide_table.Rd @@ -2,23 +2,22 @@ % Please edit documentation in R/as_wide_table.R \name{as_wide_table} \alias{as_wide_table} -\title{Create a single wide table from the AusTraits data object} +\title{Create a single wide table from a traits.build data object} \usage{ -as_wide_table(austraits) +as_wide_table(database) } \arguments{ -\item{austraits}{austraits data object} +\item{database}{traits.build database (list object)} } \value{ A single wide table with collapsed contexts and locations text and with some cols renamed for alignment with other resources } \description{ -Create a single wide table from the AusTraits data object +Create a single wide table from a traits.build data object } \examples{ \dontrun{ -data <- austraits -data \%>\% as_wide_table() +austraits \%>\% as_wide_table() } } diff --git a/man/austraits-package.Rd b/man/austraits-package.Rd index b101cdf..e1b261b 100644 --- a/man/austraits-package.Rd +++ b/man/austraits-package.Rd @@ -25,5 +25,10 @@ Authors: \item Dony Indiarto (\href{https://orcid.org/0000-0001-9546-8201}{ORCID}) } +Other contributors: +\itemize{ + \item Elizabeth Wenk \email{e.wenk@unsw.edu.au} (\href{https://orcid.org/0000-0001-5640-5910}{ORCID}) [contributor] +} + } \keyword{internal} diff --git a/man/bind_databases.Rd b/man/bind_databases.Rd new file mode 100644 index 0000000..1d8865f --- /dev/null +++ b/man/bind_databases.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/bind_databases.R +\name{bind_databases} +\alias{bind_databases} +\title{Bind multiple traits.build data objects into a single data object} +\usage{ +bind_databases(database_1, ...) +} +\arguments{ +\item{database_1}{List of traits.build databases to bind together} + +\item{...}{Arguments passed to other functions} +} +\value{ +Compiled database as a single large list +} +\description{ +\code{bind_databases} binds all the listed studies into a single traits.build +database object as a large list. +} diff --git a/man/bind_trait_values.Rd b/man/bind_trait_values.Rd index 3dc5220..d8ce4f6 100644 --- a/man/bind_trait_values.Rd +++ b/man/bind_trait_values.Rd @@ -7,7 +7,7 @@ bind_trait_values(trait_data) } \arguments{ -\item{trait_data}{The trait data frame generated from austraits - see example} +\item{trait_data}{the traits table in a traits.build database -- see example} } \value{ tibble that is condensed down where multiple observations in value, value_type and replicates are collapsed down and separated by '--' @@ -19,7 +19,7 @@ This function concatenates multiple values into a single cell \examples{ \dontrun{ traits <- austraits$traits \%>\% -dplyr::filter(dataset_id == "Falster_2005_1") +dplyr::filter(dataset_id == "ABRS_1981") traits traits_bind <- bind_trait_values(traits) } diff --git a/man/check_compatibility.Rd b/man/check_compatibility.Rd new file mode 100644 index 0000000..58581c7 --- /dev/null +++ b/man/check_compatibility.Rd @@ -0,0 +1,28 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/check_compatibility.R +\name{check_compatibility} +\alias{check_compatibility} +\title{Check compatibility of traits.build object} +\usage{ +check_compatibility(database, single_table_allowed = FALSE) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{single_table_allowed}{logical for when the input might be a single table instead of a complete database; defaults to FALSE} +} +\value{ +logical (T/F) output and messaging for uncompatible versions +} +\description{ +Function to check whether the data object has been compiled by the traits.build workflow and +therefore has a data structure that is appropriate for use with austraits functions. +} +\examples{ +\dontrun{ +check_compatibility(database) +} +} +\author{ +Elizabeth Wenk - e.wenk@unsw.edu.au +} diff --git a/man/check_traits_compatibility.Rd b/man/check_traits_compatibility.Rd new file mode 100644 index 0000000..a2dd8c9 --- /dev/null +++ b/man/check_traits_compatibility.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/check_compatibility.R +\name{check_traits_compatibility} +\alias{check_traits_compatibility} +\title{Check compatibility of traits table} +\usage{ +check_traits_compatibility(trait_data) +} +\arguments{ +\item{trait_data}{the traits table in a traits.build database} +} +\value{ +logical, TRUE indicating version traits table came from traits.build version > 1.0 +} +\description{ +Check compatibility of traits table +} diff --git a/man/convert_df_to_list.Rd b/man/convert_df_to_list.Rd new file mode 100644 index 0000000..a3e1cca --- /dev/null +++ b/man/convert_df_to_list.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{convert_df_to_list} +\alias{convert_df_to_list} +\title{Convert dataframe to list} +\usage{ +convert_df_to_list(df) +} +\arguments{ +\item{df}{A dataframe} +} +\value{ +A (yaml) list +} +\description{ +Convert a dataframe to a named list, +useful when converting a datafreme a to yaml. +} +\examples{ +convert_df_to_list(dplyr::starwars) +} diff --git a/man/convert_list_to_df1.Rd b/man/convert_list_to_df1.Rd new file mode 100644 index 0000000..b6387d9 --- /dev/null +++ b/man/convert_list_to_df1.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{convert_list_to_df1} +\alias{convert_list_to_df1} +\title{Convert list with single entries to dataframe} +\usage{ +convert_list_to_df1(my_list) +} +\arguments{ +\item{my_list}{A list with single entries} +} +\value{ +A tibble with two columns +} +\description{ +Convert a list with a single level of entries to a dataframe, +useful when converting a yaml into a dataframe. +} +\examples{ +\dontrun{ +convert_list_to_df1(as.list(dplyr::starwars)[2]) +} +} diff --git a/man/convert_list_to_df2.Rd b/man/convert_list_to_df2.Rd new file mode 100644 index 0000000..a550d53 --- /dev/null +++ b/man/convert_list_to_df2.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{convert_list_to_df2} +\alias{convert_list_to_df2} +\title{Convert list of lists to dataframe} +\usage{ +convert_list_to_df2(my_list, as_character = TRUE, on_empty = NA) +} +\arguments{ +\item{my_list}{A list of lists to dataframe} + +\item{as_character}{A logical value, indicating whether the values are read as character} + +\item{on_empty}{Value to return if my_list is NULL, NA or is length == 0, default = NA} +} +\value{ +tibble +} +\description{ +Convert a list of lists to a dataframe, +useful when converting a multi-level yaml into a dataframe. +Function required that every list have same named elements. +} +\examples{ +demo_list1 <- list(word1 = "this", word2 = "is", word3 = "an", word4 = "example", word5 = "list") +demo_list2 <- list(word1 = "and", word2 = "a", word3 = "second", word4 = "list", word5 = "also") +combined_list <- list(demo_list1, demo_list2) +convert_list_to_df2(combined_list) +} diff --git a/man/create_metadata.Rd b/man/create_metadata.Rd deleted file mode 100644 index d9880e0..0000000 --- a/man/create_metadata.Rd +++ /dev/null @@ -1,17 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/load_austraits.R -\name{create_metadata} -\alias{create_metadata} -\title{Helper function to create nice metadata table} -\usage{ -create_metadata(res) -} -\arguments{ -\item{res}{output of austraits.json} -} -\value{ -dataframe of metadata (date of release, doi and version) -} -\description{ -Helper function to create nice metadata table -} diff --git a/man/download_austraits.Rd b/man/download_austraits.Rd deleted file mode 100644 index f1760ab..0000000 --- a/man/download_austraits.Rd +++ /dev/null @@ -1,18 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/load_austraits.R -\name{download_austraits} -\alias{download_austraits} -\title{Function for loading .rds AusTraits files} -\usage{ -download_austraits(url, filename, path) -} -\arguments{ -\item{url}{url of download via Zenodo API} - -\item{filename}{Name of file that will be downloaded e.g. austraits-3.0.2.rds} - -\item{path}{file path to where AusTraits will be downloaded} -} -\description{ -Function for loading .rds AusTraits files -} diff --git a/man/extract_data.Rd b/man/extract_data.Rd new file mode 100644 index 0000000..65fc3af --- /dev/null +++ b/man/extract_data.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/extract_data.R +\name{extract_data} +\alias{extract_data} +\title{Extract data from traits.build database} +\usage{ +extract_data(database, table = NA, col, col_value) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{table}{Table within a traits.build database} + +\item{col}{Column name within the specified table.} + +\item{col_value}{Value (of column, from with a table) that is used to subset database. This can be a single value or a vector. It includes partial string matches.} +} +\value{ +subset traits.build database +} +\description{ +Function to extract data from a traits.build database based on +any value(s) from any column in the traits, locations, contexts, methods, +taxa, taxonomic_updates, and contributors tables. +The output a traits.build formatted database with all tables subset +based on the specified table, column (variable) and column value. +} +\examples{ +\dontrun{ +extract_data(database = traits.build_database, table = "traits", +col = "trait_name", col_value = "leaf_area") +} +} diff --git a/man/extract_dataset.Rd b/man/extract_dataset.Rd index 10fa594..ac1df8a 100644 --- a/man/extract_dataset.Rd +++ b/man/extract_dataset.Rd @@ -2,34 +2,36 @@ % Please edit documentation in R/extract_dataset.R \name{extract_dataset} \alias{extract_dataset} -\alias{extract_dataset1} -\alias{extract_dataset2} \title{Extract all data for a particular dataset} \usage{ -extract_dataset(austraits, dataset_id) - -extract_dataset1(austraits, dataset_id) - -extract_dataset2(austraits, dataset_id) +extract_dataset(database, dataset_id) } \arguments{ -\item{austraits}{\itemize{ -\item A large list of tibbles built from austraits -}} +\item{database}{traits.build database (list object)} -\item{dataset_id}{\itemize{ -\item character string that matches a dataset_id in the data -}} +\item{dataset_id}{character string that matches a \code{dataset_id} in the database} } \value{ -A large list of tibbles containing all austraits information for one particular dataset +List of tibbles containing all traits.build data and metadata for the specified dataset(s). } \description{ -Function to subset of all data associated with a particular dataset from austraits +Function to subset all data associated with a particular dataset from a traits.build relational database. +} +\details{ +\code{extract_dataset} has been developed to extract data for specific datasets from databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} } \examples{ \dontrun{ -extract_dataset(austraits, "Falster_2003") +extract_dataset(database, "Falster_2003") } } \author{ diff --git a/man/extract_taxa.Rd b/man/extract_taxa.Rd index 9959e3d..62b0819 100644 --- a/man/extract_taxa.Rd +++ b/man/extract_taxa.Rd @@ -2,29 +2,41 @@ % Please edit documentation in R/extract_taxa.R \name{extract_taxa} \alias{extract_taxa} -\title{Extract data for one specific taxa} +\title{Extract all data for specific taxa} \usage{ -extract_taxa(austraits, family = NULL, genus = NULL, taxon_name = NULL) +extract_taxa(database, family = NULL, genus = NULL, taxon_name = NULL) } \arguments{ -\item{austraits}{austraits list object} +\item{database}{traits.build database (list object)} -\item{family}{character string of family} +\item{family}{character string of family or families} -\item{genus}{character string of genus} +\item{genus}{character string of genus or genera} -\item{taxon_name}{character string of taxon name} +\item{taxon_name}{character string of taxon name(s)} } \value{ -A large list of tibbles containing all austraits information for specificied taxa +List of tibbles containing all traits.build data and metadata for the specified taxa. } \description{ -Function to subset of all data associated with a particular dataset from austraits +Function to subset of all data associated with a particular taxon from a traits.build relational database. +} +\details{ +\code{extract_taxa} has been developed to extract data for specific taxa from databases built using the traits.build workflow. +Learn more at: +\href{https://github.com/traitecoevo/traits.build-book}{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/database} for how to install old versions of the package or download a newer version of the database. +} } \examples{ \dontrun{ -extract_taxa(austraits, family = "Proteaceae") -extract_taxa(austraits, genus = "Acacia") +extract_taxa(database = austraits, family = "Proteaceae") +extract_taxa(database = austraits, genus = "Acacia") } } \author{ diff --git a/man/extract_trait.Rd b/man/extract_trait.Rd index 284135f..dea3d39 100644 --- a/man/extract_trait.Rd +++ b/man/extract_trait.Rd @@ -2,32 +2,38 @@ % Please edit documentation in R/extract_trait.R \name{extract_trait} \alias{extract_trait} -\title{Extract data for specific traits} +\title{Extract all data for specific traits} \usage{ -extract_trait(austraits, trait_names, taxon_names) +extract_trait(database, trait_names, taxon_names) } \arguments{ -\item{austraits}{\itemize{ -\item A large list of tibbles built from austraits -}} +\item{database}{traits.build database (list object)} -\item{trait_names}{\itemize{ -\item character string of trait that will be extracted -}} +\item{trait_names}{character string of trait(s) for which data will be extracted} -\item{taxon_names}{\itemize{ -\item optional argument -}} +\item{taxon_names}{optional argument, specifying taxa for which data will be extracted} } \value{ -A large list of tibbles containing all austraits information for one particular dataset +List of tibbles containing all traits.build data and metadata for the specified trait(s). } \description{ -Function to subset of all data associated with a particular dataset from austraits +Function to subset all data associated with a particular trait from a traits.build relational database. +} +\details{ +\code{extract_trait} has been developed to extract data for specific traits from databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} } \examples{ \dontrun{ -extract_trait(austraits, "wood_density", taxon_name = "Acacia celsa") +extract_trait(database = austraits, trait_names = "wood_density", taxon_names = "Acacia celsa") } } \author{ diff --git a/man/flatten_database.Rd b/man/flatten_database.Rd new file mode 100644 index 0000000..566c9ee --- /dev/null +++ b/man/flatten_database.Rd @@ -0,0 +1,31 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/flatten_database.R +\name{flatten_database} +\alias{flatten_database} +\title{Create combined traits.build table} +\usage{ +flatten_database(database, format, vars, include_description) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{format}{A parameter for the locations, contexts and data contributors tables specifying how data are packed. +All three can be formatted as a single compacted column(s) will have a human readable column ("single_column_pretty") +or using json ("single_column_json") syntax. For location properties or context properties there is also +the option to add each \code{location_property} or \code{context_property} to the traits table as its own column ("many_columns"); +the contributors column defaults to "single_column_pretty" when this option is selected.} + +\item{vars}{List specifying which columns or properties to include from each table. The detail is for all columns/properties to be included.} + +\item{include_description}{A logical indicating whether to include (TRUE) or omit (FALSE) the context_property descriptions; defaults to TRUE.} +} +\value{ +A table combining information in 7 traits.build relational tables: traits, locations, contexts, methods, taxa, taxonomic_updates, and contributors +} +\description{ +Create a single database output that merges together the information +in all relational tables within a traits.build database. +Trait measurements are still output in long format (1 row per trait value), +but all measurement-related metadata (methods, location properties, context properties, contributors) +are now included as additional columns in a single table. +} diff --git a/man/get_compiled_by_traits.build.Rd b/man/get_compiled_by_traits.build.Rd new file mode 100644 index 0000000..6e48555 --- /dev/null +++ b/man/get_compiled_by_traits.build.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/check_compatibility.R +\name{get_compiled_by_traits.build} +\alias{get_compiled_by_traits.build} +\title{Retrieve compiled by information from metadata table} +\usage{ +get_compiled_by_traits.build(database) +} +\arguments{ +\item{database}{traits.build database} +} +\value{ +logical, TRUE indicating version traits table came from traits.build version > 1.0 +} +\description{ +Retrieve compiled by information from metadata table +} diff --git a/man/get_traits_table.Rd b/man/get_traits_table.Rd new file mode 100644 index 0000000..60ab957 --- /dev/null +++ b/man/get_traits_table.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{get_traits_table} +\alias{get_traits_table} +\title{Retrieve traits table if user passes traits.build object.} +\usage{ +get_traits_table(database) +} +\arguments{ +\item{database}{traits.build database or traits table in a traits.build database} +} +\description{ +Retrieve traits table if user passes traits.build object. +} diff --git a/man/join_all.Rd b/man/join_all.Rd deleted file mode 100644 index ff4dd05..0000000 --- a/man/join_all.Rd +++ /dev/null @@ -1,54 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/join_all.R -\name{join_all} -\alias{join_all} -\alias{join_taxonomy} -\alias{join_methods} -\alias{join_locations} -\alias{join_contexts} -\title{Join study details into main \code{traits} dataset} -\usage{ -join_all(austraits) - -join_taxonomy(austraits, ...) - -join_methods(austraits, ...) - -join_locations(austraits, ...) - -join_contexts(austraits, ...) -} -\arguments{ -\item{austraits}{dataframe generated by austraits build} - -\item{...}{arguments passed to \code{vars} to subset the columns} -} -\value{ -austraits list object, but with additional variables appended to \code{traits} dataframe -} -\description{ -Function to append all study information (method, location, taxonomic, context) variables into trait database -} -\examples{ -\dontrun{ -austraits$traits - -#Append locations data -(austraits \%>\% join_locations)$traits - -#Append contexts -(austraits \%>\% join_contexts)$traits - -# Append methods -(austraits \%>\% join_methods(vars = c("method_id")))$traits - -#Append taxonomic details -(austraits \%>\% join_taxonomy)$traits - -#Append all information -(austraits \%>\% join_all)$traits -} -} -\author{ -Daniel Falster - daniel.falster@unsw.edu.au -} diff --git a/man/join_context_properties.Rd b/man/join_context_properties.Rd new file mode 100644 index 0000000..a661dc3 --- /dev/null +++ b/man/join_context_properties.Rd @@ -0,0 +1,46 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_context_properties} +\alias{join_context_properties} +\title{Joining context properties to traits table} +\usage{ +join_context_properties( + database, + format = "single_column_pretty", + vars = "all", + include_description = TRUE +) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{format}{Specifies whether metadata from the contexts is output in a human readable format ("single_column_pretty"; default), with each context property added as a separate column ("many_columns") or using json syntax ("single_column_json").} + +\item{vars}{Location properties for which data is to be appended to the traits table, defaulting to all context properties (vars = "all").} + +\item{include_description}{A logical indicating whether to include (TRUE) or omit (FALSE) the context_property descriptions.} +} +\value{ +traits.build list object, but context properties from the contexts table appended to the traits table. +} +\description{ +Function to merge metadata from the contexts table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +(database \%>\% join_context_properties( +format = "many_columns", vars = "all", include_description = TRUE))$traits +} +} diff --git a/man/join_contributors.Rd b/man/join_contributors.Rd new file mode 100644 index 0000000..5fb6a3b --- /dev/null +++ b/man/join_contributors.Rd @@ -0,0 +1,39 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_contributors} +\alias{join_contributors} +\title{Joining data contributor metadata to traits table} +\usage{ +join_contributors(database, format = "single_column_pretty", vars = "all") +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{format}{Specifies whether metadata from the contributors table is output in a human readable format ("single_column_pretty"; default) or using json syntax ("single_column_json").} + +\item{vars}{Columns from the taxa table to be joined to the traits table, defaulting to all columns (vars = "all").} +} +\value{ +traits.build list object, but with additional fields (columns) for the specified variables from the data contributors table appended to the traits table. +} +\description{ +Function to merge metadata from the data contributors table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +(database \%>\% join_contributors(format = "single_column_pretty", +vars = c("last_name", "first_name", "ORCID")))$traits +} +} diff --git a/man/join_location_coordinates.Rd b/man/join_location_coordinates.Rd new file mode 100644 index 0000000..708c37a --- /dev/null +++ b/man/join_location_coordinates.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_location_coordinates} +\alias{join_location_coordinates} +\title{Joining location coordinates to traits table} +\usage{ +join_location_coordinates(database) +} +\arguments{ +\item{database}{traits.build database (list object)} +} +\value{ +traits.build list object, but with additional fields (columns) +for latitude and longitude appended to \code{traits} dataframe +} +\description{ +Function to merge geographic coordinates (latitude/longitude) +stored in the locations table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +(database \%>\% join_location_coordinates)$traits +} + +} diff --git a/man/join_location_properties.Rd b/man/join_location_properties.Rd new file mode 100644 index 0000000..601ae9a --- /dev/null +++ b/man/join_location_properties.Rd @@ -0,0 +1,42 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_location_properties} +\alias{join_location_properties} +\title{Joining location properties to traits table} +\usage{ +join_location_properties( + database, + format = "single_column_pretty", + vars = "all" +) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{format}{Specifies whether metadata from the locations is output in a human readable format ("single_column_pretty"; default), with each location property added as a separate column ("many_columns") or using json syntax ("single_column_json").} + +\item{vars}{Location properties for which data is to be appended to the traits table, defaulting to all location properties (vars = "all").} +} +\value{ +traits.build list object, but location properties from the locations table appended to the traits table. +} +\description{ +Function to merge metadata from the locations table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +(database \%>\% join_location_properties(format = "single_column_pretty", vars = "all"))$traits +} +} diff --git a/man/join_methods.Rd b/man/join_methods.Rd new file mode 100644 index 0000000..aded6d0 --- /dev/null +++ b/man/join_methods.Rd @@ -0,0 +1,36 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_methods} +\alias{join_methods} +\title{Joining methodological information to traits table} +\usage{ +join_methods(database, vars = c("methods")) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{vars}{Columns from the taxa table to be joined to the traits table, defaulting to c("methods").} +} +\value{ +traits.build list object, but with additional fields (columns) for the specified variables from the methods table appended to the traits table. +} +\description{ +Function to merge metadata from the methods table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +(database \%>\% join_methods)$traits +} +} diff --git a/man/join_sites.Rd b/man/join_sites.Rd deleted file mode 100644 index 89f51ff..0000000 --- a/man/join_sites.Rd +++ /dev/null @@ -1,17 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/join_all.R -\name{join_sites} -\alias{join_sites} -\title{Joining location info for AusTraits versions <= 3.0.2} -\usage{ -join_sites(austraits, vars = c("longitude (deg)", "latitude (deg)")) -} -\arguments{ -\item{austraits}{austraits object} - -\item{vars}{variables from site table to join} -} -\description{ -\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} -Joining location info for AusTraits versions <= 3.0.2 -} diff --git a/man/join_taxa.Rd b/man/join_taxa.Rd new file mode 100644 index 0000000..7416a51 --- /dev/null +++ b/man/join_taxa.Rd @@ -0,0 +1,40 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_taxa} +\alias{join_taxa} +\title{Joining taxonomy to traits table} +\usage{ +join_taxa( + database, + vars = c("family", "genus", "taxon_rank", "establishment_means") +) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{vars}{Columns from the taxa table to be joined to the traits table, defaulting to c("family", "genus", "taxon_rank", "establishment_means").} +} +\value{ +traits.build list object, but with additional fields (columns) for the specified variables from the taxa table appended to the traits table. +} +\description{ +Function to merge metadata from the taxa table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +#Append taxonomic details +(database \%>\% join_taxa)$traits +} +} diff --git a/man/join_taxonomic_updates.Rd b/man/join_taxonomic_updates.Rd new file mode 100644 index 0000000..d96494f --- /dev/null +++ b/man/join_taxonomic_updates.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/join_.R +\name{join_taxonomic_updates} +\alias{join_taxonomic_updates} +\title{Joining taxonomic updates information to traits table} +\usage{ +join_taxonomic_updates(database, vars = c("aligned_name")) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{vars}{Columns from the taxa table to be joined to the traits table, defaulting to c("aligned_name").} +} +\value{ +traits.build list object, but with additional fields (columns) for the specified variables from the taxonomic_updates table appended to the traits table. +} +\description{ +Function to merge metadata from the taxonomic_updates table of a traits.build database into the core traits table. +} +\details{ +the \code{join_} functions have been developed to join relational tables for databases built using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} +} +\examples{ +\dontrun{ +#Append taxonomic update details +(database \%>\% join_taxonomic_updates)$traits +} +} diff --git a/man/load_json.Rd b/man/load_json.Rd deleted file mode 100644 index c469c36..0000000 --- a/man/load_json.Rd +++ /dev/null @@ -1,16 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/load_austraits.R -\name{load_json} -\alias{load_json} -\title{Load the austraits.json} -\usage{ -load_json(path, update) -} -\arguments{ -\item{path}{file path to where AusTraits will be downloaded} - -\item{update}{if TRUE, AusTraits versions .json will be re-downloaded} -} -\description{ -Load the austraits.json -} diff --git a/man/lookup_context_property.Rd b/man/lookup_context_property.Rd new file mode 100644 index 0000000..c95cf86 --- /dev/null +++ b/man/lookup_context_property.Rd @@ -0,0 +1,24 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/lookup_.R +\name{lookup_context_property} +\alias{lookup_context_property} +\title{Look up context properties} +\usage{ +lookup_context_property(database, term) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{term}{character string for context property search term} +} +\value{ +vector containing context properties that contains search term +} +\description{ +Look up context properties that contain a specific search term. +} +\examples{ +\dontrun{ +austraits \%>\% lookup_context_property("temperature") +} +} diff --git a/man/lookup_location_property.Rd b/man/lookup_location_property.Rd new file mode 100644 index 0000000..6f86a2a --- /dev/null +++ b/man/lookup_location_property.Rd @@ -0,0 +1,24 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/lookup_.R +\name{lookup_location_property} +\alias{lookup_location_property} +\title{Look up location properties} +\usage{ +lookup_location_property(database, term) +} +\arguments{ +\item{database}{traits.build database (list object)} + +\item{term}{character string for location property search term} +} +\value{ +vector containing location properties that contains search term +} +\description{ +Look up location properties that contain a specific search term. +} +\examples{ +\dontrun{ +austraits \%>\% lookup_location_property("soil") +} +} diff --git a/man/lookup_trait.Rd b/man/lookup_trait.Rd index 4cca0be..752f6d7 100644 --- a/man/lookup_trait.Rd +++ b/man/lookup_trait.Rd @@ -1,13 +1,13 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/lookup.R +% Please edit documentation in R/lookup_.R \name{lookup_trait} \alias{lookup_trait} \title{Look up a particular trait term} \usage{ -lookup_trait(austraits, term) +lookup_trait(database, term) } \arguments{ -\item{austraits}{austraits list} +\item{database}{traits.build database (list object)} \item{term}{character string for trait search term} } @@ -19,6 +19,6 @@ Look up a particular trait term } \examples{ \dontrun{ -austraits \%>\% lookup_trait("leaf") \%>\% extract_trait(austraits, .) +austraits \%>\% lookup_trait("leaf") \%>\% extract_trait(database = austraits, .) } } diff --git a/man/pipe.Rd b/man/pipe.Rd index a648c29..5fa90fe 100644 --- a/man/pipe.Rd +++ b/man/pipe.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/utils-pipe.R +% Please edit documentation in R/utils.R \name{\%>\%} \alias{\%>\%} \title{Pipe operator} diff --git a/man/plot_locations.Rd b/man/plot_locations.Rd index 760070b..896fe08 100644 --- a/man/plot_locations.Rd +++ b/man/plot_locations.Rd @@ -4,10 +4,10 @@ \alias{plot_locations} \title{Produce location maps of trait values} \usage{ -plot_locations(aus_traits, feature = "trait_name", ...) +plot_locations(database, feature = "trait_name", ...) } \arguments{ -\item{aus_traits}{austraits object OR traits table. Note location details must be joined. See join_all and examples} +\item{database}{traits.build database OR traits table from a traits.build database. Note location details must be joined. See join_location_coordinates and examples} \item{feature}{grouping/classification categories e.g trait_name, collection_type for <= v3.0.2, basis of record for >3.0.2} @@ -22,11 +22,11 @@ Plot location where trait data was collected from \examples{ \dontrun{ #All traits from a given study -data <- austraits \%>\% extract_dataset(dataset_id = "Falster_2003") \%>\% join_all() +data <- austraits \%>\% extract_dataset(dataset_id = "Falster_2003") \%>\% join_location_coordinates() data \%>\% plot_locations("trait_name") #Single trait -data <- austraits \%>\% extract_trait(trait_names = c("plant_height")) \%>\% join_all() +data <- austraits \%>\% extract_trait(trait_names = c("plant_height")) \%>\% join_location_coordinates() data$traits \%>\% plot_locations("trait_name") } } diff --git a/man/plot_site_locations.Rd b/man/plot_site_locations.Rd index 749721c..b9dca31 100644 --- a/man/plot_site_locations.Rd +++ b/man/plot_site_locations.Rd @@ -4,10 +4,10 @@ \alias{plot_site_locations} \title{Produce location maps of trait values} \usage{ -plot_site_locations(traits, feature = "trait_name", ...) +plot_site_locations(trait_data, feature = "trait_name", ...) } \arguments{ -\item{traits}{traits table with site details appended. See join_all and examples} +\item{trait_data}{traits table in a traits.build database with site details appended. See join_location_coordinates and examples} \item{feature}{grouping/classification categories e.g trait_name, collection_type for <= v3.0.2} diff --git a/man/plot_trait_distribution_beeswarm.Rd b/man/plot_trait_distribution_beeswarm.Rd index 721b0f2..3cf92a4 100644 --- a/man/plot_trait_distribution_beeswarm.Rd +++ b/man/plot_trait_distribution_beeswarm.Rd @@ -5,23 +5,23 @@ \title{Beeswarm Trait distribution} \usage{ plot_trait_distribution_beeswarm( - austraits, - plant_trait_name, + database, + trait_name, y_axis_category, highlight = NA, hide_ids = FALSE ) } \arguments{ -\item{austraits}{austraits data object} +\item{database}{traits.build database (list object)} -\item{plant_trait_name}{Name of trait to plot} +\item{trait_name}{Name of trait to plot} \item{y_axis_category}{One of \code{dataset_id}, \code{family}} -\item{highlight}{specify a group to highlight} +\item{highlight}{Specify a group to highlight} -\item{hide_ids}{add label on y_axis?} +\item{hide_ids}{Logical for whether to add a label on y_axis?} } \description{ Plots distribution of trait values by a grouping variable using ggbeeswarm package diff --git a/man/print.austraits.Rd b/man/print.traits.build.Rd similarity index 60% rename from man/print.austraits.Rd rename to man/print.traits.build.Rd index d51d8fc..0f31be8 100644 --- a/man/print.austraits.Rd +++ b/man/print.traits.build.Rd @@ -1,13 +1,13 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/print.austraits.R -\name{print.austraits} -\alias{print.austraits} +% Please edit documentation in R/print.traits.build.R +\name{print.traits.build} +\alias{print.traits.build} \title{Generic for outputting a nice summary for austraits objects} \usage{ -\method{print}{austraits}(x, ...) +\method{print}{traits.build}(x, ...) } \arguments{ -\item{x}{austraits list object} +\item{x}{traits.build database} \item{\dots}{passed to print} } diff --git a/man/separate_trait_values.Rd b/man/separate_trait_values.Rd index 94fd948..2aa0955 100644 --- a/man/separate_trait_values.Rd +++ b/man/separate_trait_values.Rd @@ -1,13 +1,13 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/seperate_trait_values.R +% Please edit documentation in R/separate_trait_values.R \name{separate_trait_values} \alias{separate_trait_values} \title{Separate bounded trait values} \usage{ -separate_trait_values(data, definitions) +separate_trait_values(trait_data, definitions) } \arguments{ -\item{data}{The trait data frame generated from austraits - see example} +\item{trait_data}{The traits table in a traits.build database - see example} \item{definitions}{The austraits definitions data frame} } @@ -20,10 +20,10 @@ This function separates values that were concatenated so that studies that have } \examples{ \dontrun{ -traits <- austraits$traits \%>\% +trait_data <- austraits$traits \%>\% dplyr::filter(dataset_id == "Falster_2005_1") -traits -traits_bind <- bind_trait_values(traits) +trait_data +traits_bind <- bind_trait_values(trait_data) separate_trait_values(traits_bind) } } diff --git a/man/summarise_austraits.Rd b/man/summarise_database.Rd similarity index 64% rename from man/summarise_austraits.Rd rename to man/summarise_database.Rd index 5bfad15..af70696 100644 --- a/man/summarise_austraits.Rd +++ b/man/summarise_database.Rd @@ -1,13 +1,13 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/summarise_austraits.R -\name{summarise_austraits} -\alias{summarise_austraits} +\name{summarise_database} +\alias{summarise_database} \title{Summarise counts for a particular variable of interest} \usage{ -summarise_austraits(austraits, var) +summarise_database(database, var) } \arguments{ -\item{austraits}{A large list of tibbles built from austraits} +\item{database}{traits.build database (list object)} \item{var}{variable you use wish to see summary of (trait_name, genus, family)} } @@ -19,7 +19,7 @@ Summarise counts for a particular variable of interest } \examples{ \dontrun{ -summarise_austraits(austraits, "trait_name") -summarise_austraits(austraits, "family") +summarise_database(database = austraits, "trait_name") +summarise_database(database = austraits, "family") } } diff --git a/man/summarise_trait_means.Rd b/man/summarise_trait_means.Rd deleted file mode 100644 index 0f5e728..0000000 --- a/man/summarise_trait_means.Rd +++ /dev/null @@ -1,23 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/summarise_trait_values.R -\name{summarise_trait_means} -\alias{summarise_trait_means} -\title{Compute mean trait values for studies that have multiple observations for a given trait} -\usage{ -summarise_trait_means(trait_data) -} -\arguments{ -\item{trait_data}{trait table for austraits list} -} -\value{ -A reduced trait table, mean values are flagged with the suffix '_summarised' in value_type -} -\description{ -Compute mean trait values for studies that have multiple observations for a given trait -} -\examples{ -\dontrun{ -data <- austraits$traits \%>\% filter(dataset_id == "Falster_2003") -data \%>\% summarise_trait_means() -} -} diff --git a/man/trait_pivot_longer.Rd b/man/trait_pivot_longer.Rd index 1d68a00..bf2ff7c 100644 --- a/man/trait_pivot_longer.Rd +++ b/man/trait_pivot_longer.Rd @@ -2,30 +2,48 @@ % Please edit documentation in R/trait_pivot_longer.R \name{trait_pivot_longer} \alias{trait_pivot_longer} -\title{Pivot wide format AusTrait data into a long format} +\title{Pivot wide format traits table into long format} \usage{ trait_pivot_longer(wide_data) } \arguments{ -\item{wide_data}{output from trait_pivot_wider. For <= v3.0.2 list object containing wide data generated,For > v3.0.2 a tibble of wide data} +\item{wide_data}{output from trait_pivot_wider.} } \value{ +A tibble in long format + A tibble in long format } \description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} trait_pivot_longer "gathers" wide format data into a "tidy" format This function converts the data into long format where observations are on different rows and the type of observation is denoted by trait name. In other words, trait_pivot_longer reverts the actions of trait_pivot_wider } \details{ \itemize{ -\item If \code{bind_trait_values} or \code{summarise_trait_means} was applied prior to \code{trait_pivot_wider} for AusTraits +\item If \code{bind_trait_values} was applied prior to \code{trait_pivot_wider} for AusTraits <= v3.0.2, \code{trait_pivot_longer} will return a tibble with fewer observations than the original traits table. \item For AusTraits version >3.0.2, \code{trait_pivot_longer} will return a tibble with fewer columns than that original traits table \itemize{ \item The excluded columns include: "unit", "replicates", "measurement_remarks", "basis_of_record", "basis_of_value" } } + +This function reverts the actions of the function austraits::trait_pivot_wider. + +It begins with a derivation of a traits.build traits table, where multiple measurements that comprise a single observation are displayed on a single row,with a column for each trait. It then converts the table into long format where measurements of multiple traits that comprise a single observation are on different rows and a column specifying the trait names is added. + +\code{trait_pivot_longer} has been developed to pivot the traits table for a database build using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: +\itemize{ +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. +} } \examples{ \dontrun{ diff --git a/man/trait_pivot_wider.Rd b/man/trait_pivot_wider.Rd index 2cdb3ab..996fc8e 100644 --- a/man/trait_pivot_wider.Rd +++ b/man/trait_pivot_wider.Rd @@ -2,31 +2,39 @@ % Please edit documentation in R/trait_pivot_wider.R \name{trait_pivot_wider} \alias{trait_pivot_wider} -\title{Pivot long format austrait data into a wide format} +\title{Pivot long format traits table into wide format} \usage{ -trait_pivot_wider(traits) +trait_pivot_wider(database) } \arguments{ -\item{traits}{The traits table from austraits list object} +\item{database}{The traits tibble from a traits.build database} } \value{ -list of five tibbles in wide format +traits.build traits table in wide format } \description{ -\code{trait_pivot_wider} "widens" long format data ("tidy data") +Function to "widen" long format data ("tidy data"). -AusTraits data is organised in a long format where observations are on different rows and the type of observation is denoted by various identifying columns (e.g trait_name, dataset_id, observation_id etc.) -This function converts the data into wide format so that each trait in it's own column. +Data in a traits.build databases' traits table are organised in a long format where each trait measurement is on a different row and measurement metadata is recorded in other columns. Multiple traits may be measured as part of a single observation and this function pivots the data wider, such that each trait is its own column. \if{html}{\out{}}Note that if two trait measurements have the same observation_id but different value types (min, mean, mode, etc.) these will be on separate rows.\if{html}{\out{}} + +The function austraits::trait_pivot_longer reverts the actions of this function. } \details{ +`trait_pivot_wider`` has been developed to pivot the traits table for a database build using the traits.build workflow. +Learn more at: +\url{https://github.com/traitecoevo/traits.build} & +\url{https://github.com/traitecoevo/traits.build-book} + +Note to AusTraits users: \itemize{ -\item For AusTraits <=v3.0.2, some studies have multiple rows of data for each observation_id, so \code{trait_pivot_wider} will return four lists (value, unit, value_type, date and replicates) with the identifying columns and trait data arranged in columns. -\item For AusTraits >3.0.2, \code{trait_pivot_wider} will return a single widen tibble, note that some meta-data columns (unit, replicates, measurement_remarks, basis_of_record, basis_of_value) will be excluded to produce a useful wide tibble. +\item This function works with AusTraits version >= 5.0.0 (from Nov 2023 release) +\item For AusTraits versions <= 4.2.0 (up to Sept 2023 release) see \url{https://github.com/traitecoevo/austraits} for how to install old versions of the package or download a newer version of the database. } } \examples{ \dontrun{ -data <- austraits$traits \%>\% filter(dataset_id == "Falster_2003") + +data <- austraits_5.0.0_lite$traits \%>\% filter(dataset_id == "Falster_2003") data #long format traits_wide <- trait_pivot_wider(data) traits_wide #wide format diff --git a/tests/testthat/Falster_2003_combined_format.csv b/tests/testthat/Falster_2003_combined_format.csv new file mode 100644 index 0000000..44301fb --- /dev/null +++ b/tests/testthat/Falster_2003_combined_format.csv @@ -0,0 +1,115 @@ +dataset_id,taxon_name,observation_id,trait_name,value,unit,entity_type,value_type,basis_of_value,replicates,basis_of_record,life_stage,population_id,individual_id,repeat_measurements_id,temporal_context_id,source_id,location_id,entity_context_id,plot_context_id,treatment_context_id,collection_date,measurement_remarks,method_id,method_context_id,original_name,location_name,latitude (deg),longitude (deg),location_properties,treatment_context_properties,plot_context_properties,entity_context_properties,temporal_context_properties,method_context_properties,methods,description,sampling_strategy,source_primary_key,source_primary_citation,source_secondary_key,source_secondary_citation,source_original_dataset_key,source_original_dataset_citation,assistants,dataset_curators,data_contributors,taxon_rank,taxonomic_status,taxonomic_dataset,taxon_name_alternatives,genus,family,binomial,trinomial,taxon_distribution,establishment_means,scientific_name,taxon_id,taxon_id_genus,taxon_id_family,scientific_name_id,aligned_name,taxonomic_resolution,aligned_name_taxon_id,aligned_name_taxonomic_status +Falster_2003,Acacia floribunda,01,leaf_area,142,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Acacia floribunda,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia floribunda,NA,"WA (naturalised), SA (naturalised), Qld, NSW, ACT (doubtfully naturalised), Vic (native and naturalised), Tas (naturalised)",native and naturalised,Acacia floribunda (Vent.) Willd.,https://id.biodiversity.org.au/node/apni/2916159,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/63165,Acacia floribunda,NA,https://id.biodiversity.org.au/node/apni/2916159,accepted +Falster_2003,Acacia floribunda,01,leaf_inclination_angle,57,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Acacia floribunda,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia floribunda,NA,"WA (naturalised), SA (naturalised), Qld, NSW, ACT (doubtfully naturalised), Vic (native and naturalised), Tas (naturalised)",native and naturalised,Acacia floribunda (Vent.) Willd.,https://id.biodiversity.org.au/node/apni/2916159,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/63165,Acacia floribunda,NA,https://id.biodiversity.org.au/node/apni/2916159,accepted +Falster_2003,Acacia floribunda,02,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Acacia floribunda,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia floribunda,NA,"WA (naturalised), SA (naturalised), Qld, NSW, ACT (doubtfully naturalised), Vic (native and naturalised), Tas (naturalised)",native and naturalised,Acacia floribunda (Vent.) Willd.,https://id.biodiversity.org.au/node/apni/2916159,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/63165,Acacia floribunda,NA,https://id.biodiversity.org.au/node/apni/2916159,accepted +Falster_2003,Acacia myrtifolia,03,leaf_area,319,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Acacia myrtifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia myrtifolia,NA,"WA, SA, Qld, NSW, Vic, Tas",native,Acacia myrtifolia (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2901160,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/162110,Acacia myrtifolia,NA,https://id.biodiversity.org.au/node/apni/2901160,accepted +Falster_2003,Acacia myrtifolia,03,leaf_inclination_angle,66.1,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Acacia myrtifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia myrtifolia,NA,"WA, SA, Qld, NSW, Vic, Tas",native,Acacia myrtifolia (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2901160,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/162110,Acacia myrtifolia,NA,https://id.biodiversity.org.au/node/apni/2901160,accepted +Falster_2003,Acacia myrtifolia,04,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Acacia myrtifolia,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia myrtifolia,NA,"WA, SA, Qld, NSW, Vic, Tas",native,Acacia myrtifolia (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2901160,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/162110,Acacia myrtifolia,NA,https://id.biodiversity.org.au/node/apni/2901160,accepted +Falster_2003,Acacia suaveolens,05,leaf_area,562,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Acacia suaveolens,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia suaveolens,NA,"SA, Qld, NSW, Vic, Tas",native,Acacia suaveolens (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2904374,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/70862,Acacia suaveolens,NA,https://id.biodiversity.org.au/node/apni/2904374,accepted +Falster_2003,Acacia suaveolens,05,leaf_inclination_angle,71.7,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Acacia suaveolens,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia suaveolens,NA,"SA, Qld, NSW, Vic, Tas",native,Acacia suaveolens (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2904374,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/70862,Acacia suaveolens,NA,https://id.biodiversity.org.au/node/apni/2904374,accepted +Falster_2003,Acacia suaveolens,06,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Acacia suaveolens,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Acacia,Fabaceae,Acacia suaveolens,NA,"SA, Qld, NSW, Vic, Tas",native,Acacia suaveolens (Sm.) Willd.,https://id.biodiversity.org.au/node/apni/2904374,https://id.biodiversity.org.au/taxon/apni/51471290,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/70862,Acacia suaveolens,NA,https://id.biodiversity.org.au/node/apni/2904374,accepted +Falster_2003,Angophora hispida,07,leaf_area,1590,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Angophora hispida,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Angophora,Myrtaceae,Angophora hispida,NA,NSW,native,Angophora hispida (Sm.) Blaxell,https://id.biodiversity.org.au/node/apni/2889602,https://id.biodiversity.org.au/taxon/apni/51439560,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/91809,Angophora hispida,NA,https://id.biodiversity.org.au/node/apni/2889602,accepted +Falster_2003,Angophora hispida,07,leaf_inclination_angle,50.8,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Angophora hispida,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Angophora,Myrtaceae,Angophora hispida,NA,NSW,native,Angophora hispida (Sm.) Blaxell,https://id.biodiversity.org.au/node/apni/2889602,https://id.biodiversity.org.au/taxon/apni/51439560,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/91809,Angophora hispida,NA,https://id.biodiversity.org.au/node/apni/2889602,accepted +Falster_2003,Angophora hispida,08,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Angophora hispida,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Angophora,Myrtaceae,Angophora hispida,NA,NSW,native,Angophora hispida (Sm.) Blaxell,https://id.biodiversity.org.au/node/apni/2889602,https://id.biodiversity.org.au/taxon/apni/51439560,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/91809,Angophora hispida,NA,https://id.biodiversity.org.au/node/apni/2889602,accepted +Falster_2003,Astrotricha floccosa,09,leaf_area,3495,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Astrotricha floccosa,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Astrotricha latifolia (pro parte misapplied) | Astrotricha latifolia (misapplied),Astrotricha,Araliaceae,Astrotricha floccosa,NA,NSW,native,Astrotricha floccosa DC.,https://id.biodiversity.org.au/node/apni/2896847,https://id.biodiversity.org.au/taxon/apni/51736769,https://id.biodiversity.org.au/taxon/apni/51736765,https://id.biodiversity.org.au/name/apni/109321,Astrotricha floccosa,NA,NA,NA +Falster_2003,Astrotricha floccosa,09,leaf_inclination_angle,31.3,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Astrotricha floccosa,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Astrotricha latifolia (pro parte misapplied) | Astrotricha latifolia (misapplied),Astrotricha,Araliaceae,Astrotricha floccosa,NA,NSW,native,Astrotricha floccosa DC.,https://id.biodiversity.org.au/node/apni/2896847,https://id.biodiversity.org.au/taxon/apni/51736769,https://id.biodiversity.org.au/taxon/apni/51736765,https://id.biodiversity.org.au/name/apni/109321,Astrotricha floccosa,NA,NA,NA +Falster_2003,Astrotricha floccosa,10,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Astrotricha floccosa,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Astrotricha latifolia (pro parte misapplied) | Astrotricha latifolia (misapplied),Astrotricha,Araliaceae,Astrotricha floccosa,NA,NSW,native,Astrotricha floccosa DC.,https://id.biodiversity.org.au/node/apni/2896847,https://id.biodiversity.org.au/taxon/apni/51736769,https://id.biodiversity.org.au/taxon/apni/51736765,https://id.biodiversity.org.au/name/apni/109321,Astrotricha floccosa,NA,NA,NA +Falster_2003,Banksia marginata,11,leaf_area,198,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Banksia marginata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia marginata,NA,"SA, NSW, ACT, Vic, Tas",native,Banksia marginata Cav.,https://id.biodiversity.org.au/taxon/apni/51445257,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108035,Banksia marginata,NA,https://id.biodiversity.org.au/taxon/apni/51445257,accepted +Falster_2003,Banksia marginata,11,leaf_inclination_angle,53.1,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Banksia marginata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia marginata,NA,"SA, NSW, ACT, Vic, Tas",native,Banksia marginata Cav.,https://id.biodiversity.org.au/taxon/apni/51445257,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108035,Banksia marginata,NA,https://id.biodiversity.org.au/taxon/apni/51445257,accepted +Falster_2003,Banksia marginata,12,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Banksia marginata,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia marginata,NA,"SA, NSW, ACT, Vic, Tas",native,Banksia marginata Cav.,https://id.biodiversity.org.au/taxon/apni/51445257,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108035,Banksia marginata,NA,https://id.biodiversity.org.au/taxon/apni/51445257,accepted +Falster_2003,Banksia oblongifolia,13,leaf_area,1061,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Banksia oblongifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia oblongifolia,NA,"Qld, NSW",native,Banksia oblongifolia Cav.,https://id.biodiversity.org.au/node/apni/2890214,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108319,Banksia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2890214,accepted +Falster_2003,Banksia oblongifolia,13,leaf_inclination_angle,45,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Banksia oblongifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia oblongifolia,NA,"Qld, NSW",native,Banksia oblongifolia Cav.,https://id.biodiversity.org.au/node/apni/2890214,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108319,Banksia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2890214,accepted +Falster_2003,Banksia oblongifolia,14,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Banksia oblongifolia,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Banksia,Proteaceae,Banksia oblongifolia,NA,"Qld, NSW",native,Banksia oblongifolia Cav.,https://id.biodiversity.org.au/node/apni/2890214,https://id.biodiversity.org.au/taxon/apni/51732900,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108319,Banksia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2890214,accepted +Falster_2003,Boronia pinnata,15,leaf_area,151,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Boronia pinnata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Boronia rivularis (pro parte misapplied) | Boronia safrolifera (pro parte misapplied) | Boronia latipinna (misapplied) | Boronia pilosa subsp. torquata (misapplied),Boronia,Rutaceae,Boronia pinnata,NA,NSW,native,Boronia pinnata Sm.,https://id.biodiversity.org.au/node/apni/2896858,https://id.biodiversity.org.au/taxon/apni/51446985,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/60829,Boronia pinnata,NA,NA,NA +Falster_2003,Boronia pinnata,15,leaf_inclination_angle,43.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Boronia pinnata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Boronia rivularis (pro parte misapplied) | Boronia safrolifera (pro parte misapplied) | Boronia latipinna (misapplied) | Boronia pilosa subsp. torquata (misapplied),Boronia,Rutaceae,Boronia pinnata,NA,NSW,native,Boronia pinnata Sm.,https://id.biodiversity.org.au/node/apni/2896858,https://id.biodiversity.org.au/taxon/apni/51446985,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/60829,Boronia pinnata,NA,NA,NA +Falster_2003,Boronia pinnata,16,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Boronia pinnata,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,Boronia rivularis (pro parte misapplied) | Boronia safrolifera (pro parte misapplied) | Boronia latipinna (misapplied) | Boronia pilosa subsp. torquata (misapplied),Boronia,Rutaceae,Boronia pinnata,NA,NSW,native,Boronia pinnata Sm.,https://id.biodiversity.org.au/node/apni/2896858,https://id.biodiversity.org.au/taxon/apni/51446985,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/60829,Boronia pinnata,NA,NA,NA +Falster_2003,Breynia oblongifolia,17,leaf_area,346,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Breynia oblongifolia,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Breynia,Phyllanthaceae,Breynia oblongifolia,NA,"Qld, NSW",native,Breynia oblongifolia (Müll.Arg.) Müll.Arg.,https://id.biodiversity.org.au/node/apni/2898881,https://id.biodiversity.org.au/taxon/apni/51291122,https://id.biodiversity.org.au/taxon/apni/51442162,https://id.biodiversity.org.au/name/apni/67150,Breynia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2898881,accepted +Falster_2003,Breynia oblongifolia,17,leaf_inclination_angle,33.7,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Breynia oblongifolia,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Breynia,Phyllanthaceae,Breynia oblongifolia,NA,"Qld, NSW",native,Breynia oblongifolia (Müll.Arg.) Müll.Arg.,https://id.biodiversity.org.au/node/apni/2898881,https://id.biodiversity.org.au/taxon/apni/51291122,https://id.biodiversity.org.au/taxon/apni/51442162,https://id.biodiversity.org.au/name/apni/67150,Breynia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2898881,accepted +Falster_2003,Breynia oblongifolia,18,leaf_compoundness,compound,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Breynia oblongifolia,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Breynia,Phyllanthaceae,Breynia oblongifolia,NA,"Qld, NSW",native,Breynia oblongifolia (Müll.Arg.) Müll.Arg.,https://id.biodiversity.org.au/node/apni/2898881,https://id.biodiversity.org.au/taxon/apni/51291122,https://id.biodiversity.org.au/taxon/apni/51442162,https://id.biodiversity.org.au/name/apni/67150,Breynia oblongifolia,NA,https://id.biodiversity.org.au/node/apni/2898881,accepted +Falster_2003,Conospermum longifolium,19,leaf_area,1363,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Conospermum longifolium,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Conospermum,Proteaceae,Conospermum longifolium,NA,NSW,native,Conospermum longifolium Sm.,https://id.biodiversity.org.au/node/apni/2891987,https://id.biodiversity.org.au/taxon/apni/51445613,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/76335,Conospermum longifolium,NA,https://id.biodiversity.org.au/node/apni/2891987,accepted +Falster_2003,Conospermum longifolium,19,leaf_inclination_angle,72.3,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Conospermum longifolium,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Conospermum,Proteaceae,Conospermum longifolium,NA,NSW,native,Conospermum longifolium Sm.,https://id.biodiversity.org.au/node/apni/2891987,https://id.biodiversity.org.au/taxon/apni/51445613,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/76335,Conospermum longifolium,NA,https://id.biodiversity.org.au/node/apni/2891987,accepted +Falster_2003,Conospermum longifolium,20,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Conospermum longifolium,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Conospermum,Proteaceae,Conospermum longifolium,NA,NSW,native,Conospermum longifolium Sm.,https://id.biodiversity.org.au/node/apni/2891987,https://id.biodiversity.org.au/taxon/apni/51445613,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/76335,Conospermum longifolium,NA,https://id.biodiversity.org.au/node/apni/2891987,accepted +Falster_2003,Epacris pulchella,21,leaf_area,5,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Epacris pulchella,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Epacris,Ericaceae,Epacris pulchella,NA,"Qld, NSW",native,Epacris pulchella Cav.,https://id.biodiversity.org.au/node/apni/2891416,https://id.biodiversity.org.au/taxon/apni/51435301,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/79402,Epacris pulchella,NA,https://id.biodiversity.org.au/node/apni/2891416,accepted +Falster_2003,Epacris pulchella,21,leaf_inclination_angle,42.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Epacris pulchella,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Epacris,Ericaceae,Epacris pulchella,NA,"Qld, NSW",native,Epacris pulchella Cav.,https://id.biodiversity.org.au/node/apni/2891416,https://id.biodiversity.org.au/taxon/apni/51435301,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/79402,Epacris pulchella,NA,https://id.biodiversity.org.au/node/apni/2891416,accepted +Falster_2003,Epacris pulchella,22,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Epacris pulchella,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Epacris,Ericaceae,Epacris pulchella,NA,"Qld, NSW",native,Epacris pulchella Cav.,https://id.biodiversity.org.au/node/apni/2891416,https://id.biodiversity.org.au/taxon/apni/51435301,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/79402,Epacris pulchella,NA,https://id.biodiversity.org.au/node/apni/2891416,accepted +Falster_2003,Eriostemon australasius,23,leaf_area,102,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eriostemon australasius,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eriostemon,Rutaceae,Eriostemon australasius,NA,"Qld, NSW",native,Eriostemon australasius Pers.,https://id.biodiversity.org.au/node/apni/2894257,https://id.biodiversity.org.au/taxon/apni/51447032,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/63723,Eriostemon australasius,NA,https://id.biodiversity.org.au/node/apni/2894257,accepted +Falster_2003,Eriostemon australasius,23,leaf_inclination_angle,62.1,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eriostemon australasius,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eriostemon,Rutaceae,Eriostemon australasius,NA,"Qld, NSW",native,Eriostemon australasius Pers.,https://id.biodiversity.org.au/node/apni/2894257,https://id.biodiversity.org.au/taxon/apni/51447032,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/63723,Eriostemon australasius,NA,https://id.biodiversity.org.au/node/apni/2894257,accepted +Falster_2003,Eriostemon australasius,24,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Eriostemon australasius,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eriostemon,Rutaceae,Eriostemon australasius,NA,"Qld, NSW",native,Eriostemon australasius Pers.,https://id.biodiversity.org.au/node/apni/2894257,https://id.biodiversity.org.au/taxon/apni/51447032,https://id.biodiversity.org.au/taxon/apni/51461748,https://id.biodiversity.org.au/name/apni/63723,Eriostemon australasius,NA,https://id.biodiversity.org.au/node/apni/2894257,accepted +Falster_2003,Corymbia gummifera,25,leaf_area,1111,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus gummifera,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Corymbia,Myrtaceae,Corymbia gummifera,NA,"Qld, NSW, Vic",native,Corymbia gummifera (Gaertn.) K.D.Hill & L.A.S.Johnson,https://id.biodiversity.org.au/taxon/apni/51439703,https://id.biodiversity.org.au/taxon/apni/51439690,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/119407,Eucalyptus gummifera,NA,https://id.biodiversity.org.au/instance/apni/51439696,nomenclatural synonym +Falster_2003,Corymbia gummifera,25,leaf_inclination_angle,59.3,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus gummifera,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Corymbia,Myrtaceae,Corymbia gummifera,NA,"Qld, NSW, Vic",native,Corymbia gummifera (Gaertn.) K.D.Hill & L.A.S.Johnson,https://id.biodiversity.org.au/taxon/apni/51439703,https://id.biodiversity.org.au/taxon/apni/51439690,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/119407,Eucalyptus gummifera,NA,https://id.biodiversity.org.au/instance/apni/51439696,nomenclatural synonym +Falster_2003,Corymbia gummifera,26,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus gummifera,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Corymbia,Myrtaceae,Corymbia gummifera,NA,"Qld, NSW, Vic",native,Corymbia gummifera (Gaertn.) K.D.Hill & L.A.S.Johnson,https://id.biodiversity.org.au/taxon/apni/51439703,https://id.biodiversity.org.au/taxon/apni/51439690,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/119407,Eucalyptus gummifera,NA,https://id.biodiversity.org.au/instance/apni/51439696,nomenclatural synonym +Falster_2003,Eucalyptus haemastoma,27,leaf_area,1831,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus haemastoma,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eucalyptus,Myrtaceae,Eucalyptus haemastoma,NA,NSW,native,Eucalyptus haemastoma Sm.,https://id.biodiversity.org.au/taxon/apni/51440615,https://id.biodiversity.org.au/taxon/apni/51738743,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/94219,Eucalyptus haemastoma,NA,https://id.biodiversity.org.au/taxon/apni/51440615,accepted +Falster_2003,Eucalyptus haemastoma,27,leaf_inclination_angle,69.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus haemastoma,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eucalyptus,Myrtaceae,Eucalyptus haemastoma,NA,NSW,native,Eucalyptus haemastoma Sm.,https://id.biodiversity.org.au/taxon/apni/51440615,https://id.biodiversity.org.au/taxon/apni/51738743,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/94219,Eucalyptus haemastoma,NA,https://id.biodiversity.org.au/taxon/apni/51440615,accepted +Falster_2003,Eucalyptus haemastoma,28,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Eucalyptus haemastoma,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Eucalyptus,Myrtaceae,Eucalyptus haemastoma,NA,NSW,native,Eucalyptus haemastoma Sm.,https://id.biodiversity.org.au/taxon/apni/51440615,https://id.biodiversity.org.au/taxon/apni/51738743,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/94219,Eucalyptus haemastoma,NA,https://id.biodiversity.org.au/taxon/apni/51440615,accepted +Falster_2003,Gompholobium latifolium,29,leaf_area,254,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Gompholobium latifolium,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Gompholobium,Fabaceae,Gompholobium latifolium,NA,"Qld, NSW, Vic",native,Gompholobium latifolium Sm.,https://id.biodiversity.org.au/node/apni/2913896,https://id.biodiversity.org.au/taxon/apni/51436123,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/79047,Gompholobium latifolium,NA,https://id.biodiversity.org.au/node/apni/2913896,accepted +Falster_2003,Gompholobium latifolium,29,leaf_inclination_angle,26.9,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Gompholobium latifolium,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Gompholobium,Fabaceae,Gompholobium latifolium,NA,"Qld, NSW, Vic",native,Gompholobium latifolium Sm.,https://id.biodiversity.org.au/node/apni/2913896,https://id.biodiversity.org.au/taxon/apni/51436123,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/79047,Gompholobium latifolium,NA,https://id.biodiversity.org.au/node/apni/2913896,accepted +Falster_2003,Gompholobium latifolium,30,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Gompholobium latifolium,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Gompholobium,Fabaceae,Gompholobium latifolium,NA,"Qld, NSW, Vic",native,Gompholobium latifolium Sm.,https://id.biodiversity.org.au/node/apni/2913896,https://id.biodiversity.org.au/taxon/apni/51436123,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/79047,Gompholobium latifolium,NA,https://id.biodiversity.org.au/node/apni/2913896,accepted +Falster_2003,Grevillea buxifolia,31,leaf_area,52,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Grevillea buxifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea buxifolia,NA,NSW,native,Grevillea buxifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2916977,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108963,Grevillea buxifolia,NA,https://id.biodiversity.org.au/node/apni/2916977,accepted +Falster_2003,Grevillea buxifolia,31,leaf_inclination_angle,47.4,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Grevillea buxifolia,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea buxifolia,NA,NSW,native,Grevillea buxifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2916977,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108963,Grevillea buxifolia,NA,https://id.biodiversity.org.au/node/apni/2916977,accepted +Falster_2003,Grevillea buxifolia,32,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Grevillea buxifolia,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea buxifolia,NA,NSW,native,Grevillea buxifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2916977,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/108963,Grevillea buxifolia,NA,https://id.biodiversity.org.au/node/apni/2916977,accepted +Falster_2003,Grevillea speciosa,33,leaf_area,108,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Grevillea speciosa,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea speciosa,NA,NSW,native,Grevillea speciosa (Knight) McGill.,https://id.biodiversity.org.au/node/apni/2911382,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/63737,Grevillea speciosa,NA,https://id.biodiversity.org.au/node/apni/2911382,accepted +Falster_2003,Grevillea speciosa,33,leaf_inclination_angle,60.1,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Grevillea speciosa,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea speciosa,NA,NSW,native,Grevillea speciosa (Knight) McGill.,https://id.biodiversity.org.au/node/apni/2911382,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/63737,Grevillea speciosa,NA,https://id.biodiversity.org.au/node/apni/2911382,accepted +Falster_2003,Grevillea speciosa,34,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Grevillea speciosa,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Grevillea,Proteaceae,Grevillea speciosa,NA,NSW,native,Grevillea speciosa (Knight) McGill.,https://id.biodiversity.org.au/node/apni/2911382,https://id.biodiversity.org.au/taxon/apni/51726302,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/63737,Grevillea speciosa,NA,https://id.biodiversity.org.au/node/apni/2911382,accepted +Falster_2003,Hakea dactyloides,35,leaf_area,882,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Hakea dactyloides,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hakea,Proteaceae,Hakea dactyloides,NA,"WA (naturalised), NSW, Vic",native and naturalised,Hakea dactyloides (Gaertn.) Cav.,https://id.biodiversity.org.au/taxon/apni/51293434,https://id.biodiversity.org.au/taxon/apni/51445456,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/68163,Hakea dactyloides,NA,https://id.biodiversity.org.au/taxon/apni/51293434,accepted +Falster_2003,Hakea dactyloides,35,leaf_inclination_angle,60.6,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Hakea dactyloides,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hakea,Proteaceae,Hakea dactyloides,NA,"WA (naturalised), NSW, Vic",native and naturalised,Hakea dactyloides (Gaertn.) Cav.,https://id.biodiversity.org.au/taxon/apni/51293434,https://id.biodiversity.org.au/taxon/apni/51445456,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/68163,Hakea dactyloides,NA,https://id.biodiversity.org.au/taxon/apni/51293434,accepted +Falster_2003,Hakea dactyloides,36,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Hakea dactyloides,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hakea,Proteaceae,Hakea dactyloides,NA,"WA (naturalised), NSW, Vic",native and naturalised,Hakea dactyloides (Gaertn.) Cav.,https://id.biodiversity.org.au/taxon/apni/51293434,https://id.biodiversity.org.au/taxon/apni/51445456,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/68163,Hakea dactyloides,NA,https://id.biodiversity.org.au/taxon/apni/51293434,accepted +Falster_2003,Hibbertia bracteata,37,leaf_area,32,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Hibbertia bracteata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hibbertia,Dilleniaceae,Hibbertia bracteata,NA,NSW,native,Hibbertia bracteata (R.Br. ex DC.) Benth.,https://id.biodiversity.org.au/node/apni/2919490,https://id.biodiversity.org.au/taxon/apni/51434912,https://id.biodiversity.org.au/taxon/apni/51434913,https://id.biodiversity.org.au/name/apni/93940,Hibbertia bracteata,NA,https://id.biodiversity.org.au/node/apni/2919490,accepted +Falster_2003,Hibbertia bracteata,37,leaf_inclination_angle,47.2,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Hibbertia bracteata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hibbertia,Dilleniaceae,Hibbertia bracteata,NA,NSW,native,Hibbertia bracteata (R.Br. ex DC.) Benth.,https://id.biodiversity.org.au/node/apni/2919490,https://id.biodiversity.org.au/taxon/apni/51434912,https://id.biodiversity.org.au/taxon/apni/51434913,https://id.biodiversity.org.au/name/apni/93940,Hibbertia bracteata,NA,https://id.biodiversity.org.au/node/apni/2919490,accepted +Falster_2003,Hibbertia bracteata,38,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Hibbertia bracteata,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Hibbertia,Dilleniaceae,Hibbertia bracteata,NA,NSW,native,Hibbertia bracteata (R.Br. ex DC.) Benth.,https://id.biodiversity.org.au/node/apni/2919490,https://id.biodiversity.org.au/taxon/apni/51434912,https://id.biodiversity.org.au/taxon/apni/51434913,https://id.biodiversity.org.au/name/apni/93940,Hibbertia bracteata,NA,https://id.biodiversity.org.au/node/apni/2919490,accepted +Falster_2003,Isopogon anemonifolius,39,leaf_area,403,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Isopogon anemonifolius,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Isopogon,Proteaceae,Isopogon anemonifolius,NA,NSW,native,Isopogon anemonifolius (Salisb.) Knight,https://id.biodiversity.org.au/node/apni/2896366,https://id.biodiversity.org.au/taxon/apni/51445473,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/83372,Isopogon anemonifolius,NA,https://id.biodiversity.org.au/node/apni/2896366,accepted +Falster_2003,Isopogon anemonifolius,39,leaf_inclination_angle,46.3,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Isopogon anemonifolius,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Isopogon,Proteaceae,Isopogon anemonifolius,NA,NSW,native,Isopogon anemonifolius (Salisb.) Knight,https://id.biodiversity.org.au/node/apni/2896366,https://id.biodiversity.org.au/taxon/apni/51445473,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/83372,Isopogon anemonifolius,NA,https://id.biodiversity.org.au/node/apni/2896366,accepted +Falster_2003,Isopogon anemonifolius,40,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Isopogon anemonifolius,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Isopogon,Proteaceae,Isopogon anemonifolius,NA,NSW,native,Isopogon anemonifolius (Salisb.) Knight,https://id.biodiversity.org.au/node/apni/2896366,https://id.biodiversity.org.au/taxon/apni/51445473,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/83372,Isopogon anemonifolius,NA,https://id.biodiversity.org.au/node/apni/2896366,accepted +Falster_2003,Kunzea capitata,41,leaf_area,8,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Kunzea capitata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Kunzea,Myrtaceae,Kunzea capitata,NA,NSW,native,Kunzea capitata (Sm.) Heynh.,https://id.biodiversity.org.au/taxon/apni/51440134,https://id.biodiversity.org.au/taxon/apni/51695251,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/61965,Kunzea capitata,NA,https://id.biodiversity.org.au/taxon/apni/51440134,accepted +Falster_2003,Kunzea capitata,41,leaf_inclination_angle,56.7,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Kunzea capitata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Kunzea,Myrtaceae,Kunzea capitata,NA,NSW,native,Kunzea capitata (Sm.) Heynh.,https://id.biodiversity.org.au/taxon/apni/51440134,https://id.biodiversity.org.au/taxon/apni/51695251,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/61965,Kunzea capitata,NA,https://id.biodiversity.org.au/taxon/apni/51440134,accepted +Falster_2003,Kunzea capitata,42,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Kunzea capitata,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Kunzea,Myrtaceae,Kunzea capitata,NA,NSW,native,Kunzea capitata (Sm.) Heynh.,https://id.biodiversity.org.au/taxon/apni/51440134,https://id.biodiversity.org.au/taxon/apni/51695251,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/61965,Kunzea capitata,NA,https://id.biodiversity.org.au/taxon/apni/51440134,accepted +Falster_2003,Lambertia formosa,43,leaf_area,60,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Lambertia formosa,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lambertia,Proteaceae,Lambertia formosa,NA,NSW,native,Lambertia formosa Sm.,https://id.biodiversity.org.au/node/apni/2920609,https://id.biodiversity.org.au/node/apni/2903088,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/115986,Lambertia formosa,NA,https://id.biodiversity.org.au/node/apni/2920609,accepted +Falster_2003,Lambertia formosa,43,leaf_inclination_angle,58.3,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Lambertia formosa,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lambertia,Proteaceae,Lambertia formosa,NA,NSW,native,Lambertia formosa Sm.,https://id.biodiversity.org.au/node/apni/2920609,https://id.biodiversity.org.au/node/apni/2903088,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/115986,Lambertia formosa,NA,https://id.biodiversity.org.au/node/apni/2920609,accepted +Falster_2003,Lambertia formosa,44,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Lambertia formosa,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lambertia,Proteaceae,Lambertia formosa,NA,NSW,native,Lambertia formosa Sm.,https://id.biodiversity.org.au/node/apni/2920609,https://id.biodiversity.org.au/node/apni/2903088,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/115986,Lambertia formosa,NA,https://id.biodiversity.org.au/node/apni/2920609,accepted +Falster_2003,Lasiopetalum ferrugineum,45,leaf_area,350,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Lasiopetalum ferrugineum,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lasiopetalum,Malvaceae,Lasiopetalum ferrugineum,NA,"Qld, NSW, Vic",native,Lasiopetalum ferrugineum Sm. ex Andrews,https://id.biodiversity.org.au/node/apni/2919266,https://id.biodiversity.org.au/taxon/apni/51438987,https://id.biodiversity.org.au/taxon/apni/51439248,https://id.biodiversity.org.au/name/apni/71623,Lasiopetalum ferrugineum,NA,https://id.biodiversity.org.au/node/apni/2919266,accepted +Falster_2003,Lasiopetalum ferrugineum,45,leaf_inclination_angle,44.6,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Lasiopetalum ferrugineum,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lasiopetalum,Malvaceae,Lasiopetalum ferrugineum,NA,"Qld, NSW, Vic",native,Lasiopetalum ferrugineum Sm. ex Andrews,https://id.biodiversity.org.au/node/apni/2919266,https://id.biodiversity.org.au/taxon/apni/51438987,https://id.biodiversity.org.au/taxon/apni/51439248,https://id.biodiversity.org.au/name/apni/71623,Lasiopetalum ferrugineum,NA,https://id.biodiversity.org.au/node/apni/2919266,accepted +Falster_2003,Lasiopetalum ferrugineum,46,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Lasiopetalum ferrugineum,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lasiopetalum,Malvaceae,Lasiopetalum ferrugineum,NA,"Qld, NSW, Vic",native,Lasiopetalum ferrugineum Sm. ex Andrews,https://id.biodiversity.org.au/node/apni/2919266,https://id.biodiversity.org.au/taxon/apni/51438987,https://id.biodiversity.org.au/taxon/apni/51439248,https://id.biodiversity.org.au/name/apni/71623,Lasiopetalum ferrugineum,NA,https://id.biodiversity.org.au/node/apni/2919266,accepted +Falster_2003,Leptospermum sp. [Falster_2003],47,leaf_area,20,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum spp,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",genus,genus accepted,APC,NA,Leptospermum,Myrtaceae,NA,NA,NA,NA,NA,NA,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,NA,Leptospermum sp. [Falster_2003],genus,NA,NA +Falster_2003,Leptospermum sp. [Falster_2003],47,leaf_inclination_angle,67.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum spp,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",genus,genus accepted,APC,NA,Leptospermum,Myrtaceae,NA,NA,NA,NA,NA,NA,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,NA,Leptospermum sp. [Falster_2003],genus,NA,NA +Falster_2003,Leptospermum sp. [Falster_2003],48,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum spp,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",genus,genus accepted,APC,NA,Leptospermum,Myrtaceae,NA,NA,NA,NA,NA,NA,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,NA,Leptospermum sp. [Falster_2003],genus,NA,NA +Falster_2003,Leptospermum trinervium,49,leaf_area,55,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum trinervium,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leptospermum,Myrtaceae,Leptospermum trinervium,NA,"Qld, NSW, ACT, Vic",native,Leptospermum trinervium (J.White) Joy Thomps.,https://id.biodiversity.org.au/node/apni/2908252,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/101750,Leptospermum trinervium,NA,https://id.biodiversity.org.au/node/apni/2908252,accepted +Falster_2003,Leptospermum trinervium,49,leaf_inclination_angle,58.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum trinervium,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leptospermum,Myrtaceae,Leptospermum trinervium,NA,"Qld, NSW, ACT, Vic",native,Leptospermum trinervium (J.White) Joy Thomps.,https://id.biodiversity.org.au/node/apni/2908252,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/101750,Leptospermum trinervium,NA,https://id.biodiversity.org.au/node/apni/2908252,accepted +Falster_2003,Leptospermum trinervium,50,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Leptospermum trinervium,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leptospermum,Myrtaceae,Leptospermum trinervium,NA,"Qld, NSW, ACT, Vic",native,Leptospermum trinervium (J.White) Joy Thomps.,https://id.biodiversity.org.au/node/apni/2908252,https://id.biodiversity.org.au/taxon/apni/51440260,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/101750,Leptospermum trinervium,NA,https://id.biodiversity.org.au/node/apni/2908252,accepted +Falster_2003,Leucopogon microphyllus,51,leaf_area,1,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leucopogon microphyllus,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leucopogon,Ericaceae,Leucopogon microphyllus,NA,"Qld, NSW, ACT, Vic",native,Leucopogon microphyllus (Cav.) R.Br.,https://id.biodiversity.org.au/node/apni/2888801,https://id.biodiversity.org.au/taxon/apni/51435325,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/111371,Leucopogon microphyllus,NA,https://id.biodiversity.org.au/node/apni/2888801,accepted +Falster_2003,Leucopogon microphyllus,51,leaf_inclination_angle,52.4,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Leucopogon microphyllus,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leucopogon,Ericaceae,Leucopogon microphyllus,NA,"Qld, NSW, ACT, Vic",native,Leucopogon microphyllus (Cav.) R.Br.,https://id.biodiversity.org.au/node/apni/2888801,https://id.biodiversity.org.au/taxon/apni/51435325,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/111371,Leucopogon microphyllus,NA,https://id.biodiversity.org.au/node/apni/2888801,accepted +Falster_2003,Leucopogon microphyllus,52,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Leucopogon microphyllus,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Leucopogon,Ericaceae,Leucopogon microphyllus,NA,"Qld, NSW, ACT, Vic",native,Leucopogon microphyllus (Cav.) R.Br.,https://id.biodiversity.org.au/node/apni/2888801,https://id.biodiversity.org.au/taxon/apni/51435325,https://id.biodiversity.org.au/taxon/apni/51738121,https://id.biodiversity.org.au/name/apni/111371,Leucopogon microphyllus,NA,https://id.biodiversity.org.au/node/apni/2888801,accepted +Falster_2003,Lomatia silaifolia,53,leaf_area,3950,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Lomatia siliafolia,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lomatia,Proteaceae,Lomatia silaifolia,NA,"Qld, NSW",native,Lomatia silaifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2897191,https://id.biodiversity.org.au/taxon/apni/51445482,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/95180,Lomatia silaifolia,species,https://id.biodiversity.org.au/node/apni/2897191,accepted +Falster_2003,Lomatia silaifolia,53,leaf_inclination_angle,47.9,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Lomatia siliafolia,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lomatia,Proteaceae,Lomatia silaifolia,NA,"Qld, NSW",native,Lomatia silaifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2897191,https://id.biodiversity.org.au/taxon/apni/51445482,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/95180,Lomatia silaifolia,species,https://id.biodiversity.org.au/node/apni/2897191,accepted +Falster_2003,Lomatia silaifolia,54,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Lomatia siliafolia,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Lomatia,Proteaceae,Lomatia silaifolia,NA,"Qld, NSW",native,Lomatia silaifolia (Sm.) R.Br.,https://id.biodiversity.org.au/node/apni/2897191,https://id.biodiversity.org.au/taxon/apni/51445482,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/95180,Lomatia silaifolia,species,https://id.biodiversity.org.au/node/apni/2897191,accepted +Falster_2003,Persoonia lanceolata,55,leaf_area,504,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Persoonia lanceolata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia lanceolata,NA,NSW,native,Persoonia lanceolata Andrews,https://id.biodiversity.org.au/node/apni/2892213,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113365,Persoonia lanceolata,NA,https://id.biodiversity.org.au/node/apni/2892213,accepted +Falster_2003,Persoonia lanceolata,55,leaf_inclination_angle,64.9,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Persoonia lanceolata,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia lanceolata,NA,NSW,native,Persoonia lanceolata Andrews,https://id.biodiversity.org.au/node/apni/2892213,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113365,Persoonia lanceolata,NA,https://id.biodiversity.org.au/node/apni/2892213,accepted +Falster_2003,Persoonia lanceolata,56,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Persoonia lanceolata,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia lanceolata,NA,NSW,native,Persoonia lanceolata Andrews,https://id.biodiversity.org.au/node/apni/2892213,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113365,Persoonia lanceolata,NA,https://id.biodiversity.org.au/node/apni/2892213,accepted +Falster_2003,Persoonia levis,57,leaf_area,1957,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Persoonia levis,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia levis,NA,"NSW, Vic",native,Persoonia levis (Cav.) Domin,https://id.biodiversity.org.au/node/apni/2920199,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113337,Persoonia levis,NA,https://id.biodiversity.org.au/node/apni/2920199,accepted +Falster_2003,Persoonia levis,57,leaf_inclination_angle,73.5,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Persoonia levis,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia levis,NA,"NSW, Vic",native,Persoonia levis (Cav.) Domin,https://id.biodiversity.org.au/node/apni/2920199,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113337,Persoonia levis,NA,https://id.biodiversity.org.au/node/apni/2920199,accepted +Falster_2003,Persoonia levis,58,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Persoonia levis,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Persoonia,Proteaceae,Persoonia levis,NA,"NSW, Vic",native,Persoonia levis (Cav.) Domin,https://id.biodiversity.org.au/node/apni/2920199,https://id.biodiversity.org.au/taxon/apni/51429033,https://id.biodiversity.org.au/taxon/apni/51732901,https://id.biodiversity.org.au/name/apni/113337,Persoonia levis,NA,https://id.biodiversity.org.au/node/apni/2920199,accepted +Falster_2003,Phyllota phylicoides,59,leaf_area,16,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Phyllota phylicoides,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Phyllota,Fabaceae,Phyllota phylicoides,NA,"Qld, NSW",native,Phyllota phylicoides (Sieber ex DC.) Benth.,https://id.biodiversity.org.au/taxon/apni/51429088,https://id.biodiversity.org.au/taxon/apni/51429089,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/96761,Phyllota phylicoides,NA,https://id.biodiversity.org.au/taxon/apni/51429088,accepted +Falster_2003,Phyllota phylicoides,59,leaf_inclination_angle,49.3,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Phyllota phylicoides,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Phyllota,Fabaceae,Phyllota phylicoides,NA,"Qld, NSW",native,Phyllota phylicoides (Sieber ex DC.) Benth.,https://id.biodiversity.org.au/taxon/apni/51429088,https://id.biodiversity.org.au/taxon/apni/51429089,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/96761,Phyllota phylicoides,NA,https://id.biodiversity.org.au/taxon/apni/51429088,accepted +Falster_2003,Phyllota phylicoides,60,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Phyllota phylicoides,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Phyllota,Fabaceae,Phyllota phylicoides,NA,"Qld, NSW",native,Phyllota phylicoides (Sieber ex DC.) Benth.,https://id.biodiversity.org.au/taxon/apni/51429088,https://id.biodiversity.org.au/taxon/apni/51429089,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/96761,Phyllota phylicoides,NA,https://id.biodiversity.org.au/taxon/apni/51429088,accepted +Falster_2003,Pomaderris ferruginea,61,leaf_area,1138,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Pomaderris ferruginea,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pomaderris,Rhamnaceae,Pomaderris ferruginea,NA,"Qld, NSW, Vic",native,Pomaderris ferruginea Sieber ex Fenzl,https://id.biodiversity.org.au/node/apni/2915166,https://id.biodiversity.org.au/taxon/apni/51446234,https://id.biodiversity.org.au/taxon/apni/51446206,https://id.biodiversity.org.au/name/apni/93990,Pomaderris ferruginea,NA,https://id.biodiversity.org.au/node/apni/2915166,accepted +Falster_2003,Pomaderris ferruginea,61,leaf_inclination_angle,31.8,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Pomaderris ferruginea,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pomaderris,Rhamnaceae,Pomaderris ferruginea,NA,"Qld, NSW, Vic",native,Pomaderris ferruginea Sieber ex Fenzl,https://id.biodiversity.org.au/node/apni/2915166,https://id.biodiversity.org.au/taxon/apni/51446234,https://id.biodiversity.org.au/taxon/apni/51446206,https://id.biodiversity.org.au/name/apni/93990,Pomaderris ferruginea,NA,https://id.biodiversity.org.au/node/apni/2915166,accepted +Falster_2003,Pomaderris ferruginea,62,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Pomaderris ferruginea,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pomaderris,Rhamnaceae,Pomaderris ferruginea,NA,"Qld, NSW, Vic",native,Pomaderris ferruginea Sieber ex Fenzl,https://id.biodiversity.org.au/node/apni/2915166,https://id.biodiversity.org.au/taxon/apni/51446234,https://id.biodiversity.org.au/taxon/apni/51446206,https://id.biodiversity.org.au/name/apni/93990,Pomaderris ferruginea,NA,https://id.biodiversity.org.au/node/apni/2915166,accepted +Falster_2003,Pultenaea daphnoides,63,leaf_area,153,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea daphnoides,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea daphnoides,NA,"SA, Qld, NSW, Vic, Tas",native,Pultenaea daphnoides J.C.Wendl.,https://id.biodiversity.org.au/node/apni/2909053,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/58650,Pultenaea daphnoides,NA,https://id.biodiversity.org.au/node/apni/2909053,accepted +Falster_2003,Pultenaea daphnoides,63,leaf_inclination_angle,36.7,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea daphnoides,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea daphnoides,NA,"SA, Qld, NSW, Vic, Tas",native,Pultenaea daphnoides J.C.Wendl.,https://id.biodiversity.org.au/node/apni/2909053,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/58650,Pultenaea daphnoides,NA,https://id.biodiversity.org.au/node/apni/2909053,accepted +Falster_2003,Pultenaea daphnoides,64,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea daphnoides,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea daphnoides,NA,"SA, Qld, NSW, Vic, Tas",native,Pultenaea daphnoides J.C.Wendl.,https://id.biodiversity.org.au/node/apni/2909053,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/58650,Pultenaea daphnoides,NA,https://id.biodiversity.org.au/node/apni/2909053,accepted +Falster_2003,Pultenaea tuberculata,65,leaf_area,28,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea elliptica,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea tuberculata,NA,NSW,native,Pultenaea tuberculata Pers.,https://id.biodiversity.org.au/node/apni/2915405,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62958,Pultenaea elliptica,NA,https://id.biodiversity.org.au/instance/apni/824257,taxonomic synonym +Falster_2003,Pultenaea tuberculata,65,leaf_inclination_angle,40.8,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea elliptica,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea tuberculata,NA,NSW,native,Pultenaea tuberculata Pers.,https://id.biodiversity.org.au/node/apni/2915405,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62958,Pultenaea elliptica,NA,https://id.biodiversity.org.au/instance/apni/824257,taxonomic synonym +Falster_2003,Pultenaea tuberculata,66,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea elliptica,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea tuberculata,NA,NSW,native,Pultenaea tuberculata Pers.,https://id.biodiversity.org.au/node/apni/2915405,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62958,Pultenaea elliptica,NA,https://id.biodiversity.org.au/instance/apni/824257,taxonomic synonym +Falster_2003,Pultenaea stipularis,67,leaf_area,36,mm2,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea stipularis,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea stipularis,NA,NSW,native,Pultenaea stipularis Sm.,https://id.biodiversity.org.au/node/apni/2916668,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62344,Pultenaea stipularis,NA,https://id.biodiversity.org.au/node/apni/2916668,accepted +Falster_2003,Pultenaea stipularis,67,leaf_inclination_angle,62.6,deg,population,mean,measurement,3,field,adult,01,NA,NA,NA,NA,02,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea stipularis,Ku-ring-gai Chase National Park low nutrient,-33.69389,151.1431,"description==fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs;; geology (parent material)==derived from Hawkesbury Sandstone;; leaf area index==medium;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==94",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea stipularis,NA,NSW,native,Pultenaea stipularis Sm.,https://id.biodiversity.org.au/node/apni/2916668,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62344,Pultenaea stipularis,NA,https://id.biodiversity.org.au/node/apni/2916668,accepted +Falster_2003,Pultenaea stipularis,68,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Pultenaea stipularis,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Pultenaea,Fabaceae,Pultenaea stipularis,NA,NSW,native,Pultenaea stipularis Sm.,https://id.biodiversity.org.au/node/apni/2916668,https://id.biodiversity.org.au/taxon/apni/51436286,https://id.biodiversity.org.au/taxon/apni/51702961,https://id.biodiversity.org.au/name/apni/62344,Pultenaea stipularis,NA,https://id.biodiversity.org.au/node/apni/2916668,accepted +Falster_2003,Myrsine variabilis,69,leaf_area,1994,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Rapanea variabilis,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Myrsine,Primulaceae,Myrsine variabilis,NA,"Qld, NSW",native,Myrsine variabilis R.Br.,https://id.biodiversity.org.au/node/apni/2906517,https://id.biodiversity.org.au/node/apni/2896339,https://id.biodiversity.org.au/taxon/apni/51445200,https://id.biodiversity.org.au/name/apni/86626,Rapanea variabilis,NA,https://id.biodiversity.org.au/instance/apni/852151,nomenclatural synonym +Falster_2003,Myrsine variabilis,69,leaf_inclination_angle,33.6,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Rapanea variabilis,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Myrsine,Primulaceae,Myrsine variabilis,NA,"Qld, NSW",native,Myrsine variabilis R.Br.,https://id.biodiversity.org.au/node/apni/2906517,https://id.biodiversity.org.au/node/apni/2896339,https://id.biodiversity.org.au/taxon/apni/51445200,https://id.biodiversity.org.au/name/apni/86626,Rapanea variabilis,NA,https://id.biodiversity.org.au/instance/apni/852151,nomenclatural synonym +Falster_2003,Myrsine variabilis,70,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Rapanea variabilis,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Myrsine,Primulaceae,Myrsine variabilis,NA,"Qld, NSW",native,Myrsine variabilis R.Br.,https://id.biodiversity.org.au/node/apni/2906517,https://id.biodiversity.org.au/node/apni/2896339,https://id.biodiversity.org.au/taxon/apni/51445200,https://id.biodiversity.org.au/name/apni/86626,Rapanea variabilis,NA,https://id.biodiversity.org.au/instance/apni/852151,nomenclatural synonym +Falster_2003,Syncarpia glomulifera,71,leaf_area,1158,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Syncarpia glomulifera,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Syncarpia,Myrtaceae,Syncarpia glomulifera,NA,"Qld, NSW",native,Syncarpia glomulifera (Sm.) Nied.,https://id.biodiversity.org.au/node/apni/2900963,https://id.biodiversity.org.au/node/apni/2893498,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/63895,Syncarpia glomulifera,NA,https://id.biodiversity.org.au/node/apni/2900963,accepted +Falster_2003,Syncarpia glomulifera,71,leaf_inclination_angle,36.2,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Syncarpia glomulifera,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Syncarpia,Myrtaceae,Syncarpia glomulifera,NA,"Qld, NSW",native,Syncarpia glomulifera (Sm.) Nied.,https://id.biodiversity.org.au/node/apni/2900963,https://id.biodiversity.org.au/node/apni/2893498,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/63895,Syncarpia glomulifera,NA,https://id.biodiversity.org.au/node/apni/2900963,accepted +Falster_2003,Syncarpia glomulifera,72,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Syncarpia glomulifera,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Syncarpia,Myrtaceae,Syncarpia glomulifera,NA,"Qld, NSW",native,Syncarpia glomulifera (Sm.) Nied.,https://id.biodiversity.org.au/node/apni/2900963,https://id.biodiversity.org.au/node/apni/2893498,https://id.biodiversity.org.au/taxon/apni/51738744,https://id.biodiversity.org.au/name/apni/63895,Syncarpia glomulifera,NA,https://id.biodiversity.org.au/node/apni/2900963,accepted +Falster_2003,Synoum glandulosum,73,leaf_area,1153,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Synoum glandulosum,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Synoum,Meliaceae,Synoum glandulosum,NA,"Qld, NSW",native,Synoum glandulosum (Sm.) A.Juss.,https://id.biodiversity.org.au/node/apni/2905966,https://id.biodiversity.org.au/node/apni/2908290,https://id.biodiversity.org.au/node/apni/9261145,https://id.biodiversity.org.au/name/apni/64428,Synoum glandulosum,NA,https://id.biodiversity.org.au/node/apni/2905966,accepted +Falster_2003,Synoum glandulosum,73,leaf_inclination_angle,42.3,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Synoum glandulosum,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Synoum,Meliaceae,Synoum glandulosum,NA,"Qld, NSW",native,Synoum glandulosum (Sm.) A.Juss.,https://id.biodiversity.org.au/node/apni/2905966,https://id.biodiversity.org.au/node/apni/2908290,https://id.biodiversity.org.au/node/apni/9261145,https://id.biodiversity.org.au/name/apni/64428,Synoum glandulosum,NA,https://id.biodiversity.org.au/node/apni/2905966,accepted +Falster_2003,Synoum glandulosum,74,leaf_compoundness,compound,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Synoum glandulosum,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",species,accepted,APC,NA,Synoum,Meliaceae,Synoum glandulosum,NA,"Qld, NSW",native,Synoum glandulosum (Sm.) A.Juss.,https://id.biodiversity.org.au/node/apni/2905966,https://id.biodiversity.org.au/node/apni/2908290,https://id.biodiversity.org.au/node/apni/9261145,https://id.biodiversity.org.au/name/apni/64428,Synoum glandulosum,NA,https://id.biodiversity.org.au/node/apni/2905966,accepted +Falster_2003,Trema tomentosa var. aspera,75,leaf_area,1566,mm2,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Trema aspera,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. Aggregate descriptors of tufts were total leaf area, average leaf size, leaf number, tuft ellipsoidal area, tuft depth, main axis length (length of stem from tip to the oldest leaf ), total stem length, average branch inclination (angle of stems/branches from the horizontal) and branching bifurcation angles","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",variety,accepted,APC,NA,Trema,Cannabaceae,Trema tomentosa,Trema tomentosa var. aspera,"WA, Qld, NSW, Vic (presumed extinct)",native,Trema tomentosa var. aspera (Brongn.) Hewson,https://id.biodiversity.org.au/node/apni/2917190,https://id.biodiversity.org.au/node/apni/2913617,https://id.biodiversity.org.au/taxon/apni/51269919,https://id.biodiversity.org.au/name/apni/206199,Trema aspera,NA,https://id.biodiversity.org.au/instance/apni/856997,nomenclatural synonym +Falster_2003,Trema tomentosa var. aspera,75,leaf_inclination_angle,67.2,deg,population,mean,measurement,3,field,adult,02,NA,NA,NA,NA,01,NA,NA,NA,2000/2001,NA,01,NA,Trema aspera,Ku-ring-gai Chase National Park high nutrient,-33.57889,151.2922,"description==fire-sensitive closed forest, with an overstorey to 20 m;; geology (parent material)==weathered volcanic dyke;; leaf area index==low;; precipitation, MAP (mm)==1220;; soil P, total (mg/kg)==440",NA,NA,NA,NA,NA,"For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. The three-dimensional leaf arrangement of each plant was recorded using a FASTRAK 3D-digitizer (Polhemus, Colchester, VT, USA), in conjunction with the software package FLORADIG (CSIRO Entomology, Brisbane, Australia). The digitizer includes a magnetic signal receiver and pointer, allowing the user to record the 3D spatial co-ordinates of the pointer within a hemisphere of 3 m diameter from the receiver. Individual plants are digitally reconstructed by recording a series of point co-ordinates, and the relevant connectivity between points. Stem segments and petioles are characterized by their elevation angle, azimuth, length and diameter. Individual leaves are characterized by their length together with the azimuth and elevation angle of two vectors on the lamina surface. YPLANT software (Pearcy & Yang, 1996) was used to estimate light interception and a potential carbon gain for different sample periods throughout a single day and integrated across entire days. The 3D description of leaf arrangement recorded for each tuft in FLORADIG was converted to the appropriate YPLANT format using a program written in C. Sampling time for individual tufts ranged from 20 min to 2.5 h, depending on the number and size of leaves. Although still time consuming, the methods presented here represent a marked acceleration of data collection in architectural studies using the YPLANT software. Full details regarding the collection of architectural information are given in Appendix S1.","Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",variety,accepted,APC,NA,Trema,Cannabaceae,Trema tomentosa,Trema tomentosa var. aspera,"WA, Qld, NSW, Vic (presumed extinct)",native,Trema tomentosa var. aspera (Brongn.) Hewson,https://id.biodiversity.org.au/node/apni/2917190,https://id.biodiversity.org.au/node/apni/2913617,https://id.biodiversity.org.au/taxon/apni/51269919,https://id.biodiversity.org.au/name/apni/206199,Trema aspera,NA,https://id.biodiversity.org.au/instance/apni/856997,nomenclatural synonym +Falster_2003,Trema tomentosa var. aspera,76,leaf_compoundness,simple,NA,species,mode,expert_score,NA,field,adult,NA,NA,NA,NA,NA,NA,NA,NA,NA,2000/2001,NA,01,NA,Trema aspera,NA,NA,NA,NA,NA,NA,NA,NA,NA,expert opinion,"Study relating variation in architectural properties (leaf angle and leaf size) to cross-species patterns of leaf display, light capture and simulated carbon gain in branching-units of 38 perennial species occurring at two sites in Australian forest.","Two sites were chosen within Ku-ring-gai Chase National Park, Sydney, Australia. Both were temperate forest with a high diversity of shrub species under a moderately open eucalypt canopy. The sites differed in soil fertility (94 vs 440 mg kg-1 total P - Wright et al ., 2001) but had similar average annual rainfall (1220 mm distributed throughout the year) and temperature (22 deg , 13 deg C). The vegetation at the low nutrient site (33 deg 41' 38''S, 151 deg 8'35''E) was fire-prone low open sclerophyll woodland with a species rich understorey of woody shrubs, and emergent eucalypts to 15 m (Rice & Westoby, 1983). The site was last burnt in 1990. The soils are derived from Hawkesbury Sandstone parent material. The vegetation at the higher nutrient site (33 deg 34'44''S, 151 deg 17'32''E) is fire-sensitive closed forest, with an overstorey to 20 m dominated by Syncarpia glomulifera , Eucalyptus umbra and Livistona australis . Woody shrubs, climbers, ferns and cycads dominate the understorey. The soils are derived from a weathered volcanic dyke. Plant growth is continuous throughout the year, although species may exhibit a flush of new growth in spring. Further site details are provided by (Wright et al ., 2001). Hereafter, the sites are referred to as medium LAI (closed forest) and low LAI (open woodland) sites. Sampling At either site, a large number of small to moderate-sized woody perennial shrub species coexist in a similar light environment. Most species exhibit a rigid, sclerophyllous architecture, with comparatively little scope for diurnal or seasonal variation in leaf arrangement (pers. obs.). All species with flat or simply folded leaves, as assumed by the YPLANT software, were chosen for study. This included 26 species from the low LAI and 12 from the medium LAI site. The first three undamaged individuals of each species encountered further than 10 m away from an access track were sampled. Data were collected between 20 September 2000 and 26 November 2001. For each individual, architectural information about the leading vertical branching unit, or 'tuft', on each plant was recorded. A tuft was defined as all leaves and side branches back to the oldest leaf along a leaf age sequence. This level of organisation represents an intermediate scale between the leaf and the whole plant, spanning the full range of leaf ages and reflecting the tendency for plants to consist of repeated architectural units. Tufts, as opposed to whole plants, were sampled for practical reasons and in an attempt to provide a sizeindependent unit of comparison across species. For each individual a 3D description of the tuft leaf arrangement, basal and terminal stem diameters (vernier calipers) and plant height were recorded.",Falster_2003,"D. S. Falster and M. Westoby. “Leaf size and angle vary widely across species: what consequences for light interception?”. _New Phytologist_ 158.3 (2003), pp. 509-525. doi: [10.1046/j.1469-8137.2003.00765.x](https://doi.org/10.1046%2Fj.1469-8137.2003.00765.x).",NA,NA,NA,NA,NA,Elizabeth Wenk,"Falster, Daniel <>;; Westoby, Mark <>",variety,accepted,APC,NA,Trema,Cannabaceae,Trema tomentosa,Trema tomentosa var. aspera,"WA, Qld, NSW, Vic (presumed extinct)",native,Trema tomentosa var. aspera (Brongn.) Hewson,https://id.biodiversity.org.au/node/apni/2917190,https://id.biodiversity.org.au/node/apni/2913617,https://id.biodiversity.org.au/taxon/apni/51269919,https://id.biodiversity.org.au/name/apni/206199,Trema aspera,NA,https://id.biodiversity.org.au/instance/apni/856997,nomenclatural synonym diff --git a/tests/testthat/test-as_wide_table.R b/tests/testthat/test-as_wide_table.R index 42d439b..6743310 100644 --- a/tests/testthat/test-as_wide_table.R +++ b/tests/testthat/test-as_wide_table.R @@ -1,22 +1,12 @@ -library(purrr) -austraits <- list(austraits_3.0.2_lite, - austraits_4.2.0_lite, - austraits_5.0.0_lite) - -test_widetable_success <- function(austraits){ - test_that("Function is working", { - expect_visible(austraits %>% as_wide_table()) - out <- austraits %>% as_wide_table() +test_that("Function is working", { + expect_visible(austraits_5.0.0_lite %>% as_wide_table()) + out <- austraits_5.0.0_lite %>% as_wide_table() expect_named(out) expect_type(out, "list") # "Output is correct" - expect_gt(out %>% ncol(), expected = austraits$traits %>% ncol()) + expect_gt(out %>% ncol(), expected = austraits_5.0.0_lite$traits %>% ncol()) }) -} -walk(austraits, - test_widetable_success) - expect_error(as_wide_table()) diff --git a/tests/testthat/test-austraits_load_.R b/tests/testthat/test-austraits_load_.R index 7f1ad54..c4eb528 100644 --- a/tests/testthat/test-austraits_load_.R +++ b/tests/testthat/test-austraits_load_.R @@ -1,4 +1,3 @@ -library(purrr) versions <- c("3.0.2", "4.2.0", "5.0.0") path = "ignore/data/austraits" @@ -14,7 +13,7 @@ test_get_versions <- function(version, path){ }) } -walk(versions, +purrr::walk(versions, ~ test_get_versions(.x, path)) @@ -29,7 +28,7 @@ test_load_austraits <- function(version, path){ }) } -map(versions, +purrr::map(versions, ~ test_load_austraits(.x, path = path)) diff --git a/tests/testthat/test-bind_databases.R b/tests/testthat/test-bind_databases.R new file mode 100644 index 0000000..a501274 --- /dev/null +++ b/tests/testthat/test-bind_databases.R @@ -0,0 +1,35 @@ +Banksia_1 <- austraits_5.0.0_lite %>% extract_taxa(taxon_name = "Banksia serrata") +Banksia_2 <- austraits_5.0.0_lite %>% extract_taxa(taxon_name = "Banksia ericifolia") +fire <- austraits_5.0.0_lite %>% extract_data(table = "contexts", col = "context_property", col_value = "fire") +season <- austraits_5.0.0_lite %>% extract_data(table = "contexts", col = "context_property", col_value = "season") + +test_that("Function runs", { + expect_silent(bind_databases(Banksia_1)) + expect_silent(bind_databases(Banksia_1, Banksia_2)) + expect_silent(bind_databases(fire, season)) +} +) + +test_that("Function returned expected number of rows", { + expect_equal(nrow(bind_databases(Banksia_1)$traits), nrow(Banksia_1$traits)) + expect_lt(nrow(bind_databases(fire, season)$traits), nrow(fire$traits)+nrow(season$traits)) + expect_equal(nrow(bind_databases(Banksia_1, Banksia_2)$traits), nrow(Banksia_1$traits)+nrow(Banksia_2$traits)) + expect_lt(nrow(bind_databases(Banksia_1, Banksia_2)$contexts), nrow(Banksia_1$contexts)+nrow(Banksia_2$contexts)) + expect_lt(nrow(bind_databases(Banksia_1, Banksia_2, fire, season)$contexts), nrow(Banksia_1$contexts)+nrow(Banksia_2$contexts)+nrow(fire$contexts)+nrow(season$contexts)) +} +) + +test_that("Order of tables has not changed", { + expect_equal(names(bind_databases(Banksia_1, Banksia_2)), names(austraits_5.0.0_lite)) + expect_equal(names(bind_databases(fire, season)), names(austraits_5.0.0_lite)) + expect_equal(names(bind_databases(Banksia_1, fire)), names(austraits_5.0.0_lite)) +} +) + +test_that("Number of columns has not changed", { + more_Banksia <- bind_databases(Banksia_1, Banksia_2) + expect_equal(names(more_Banksia$traits), names(austraits_5.0.0_lite$traits)) + expect_equal(names(more_Banksia$contexts), names(austraits_5.0.0_lite$contexts)) + expect_equal(sort(names(more_Banksia$definitions)), sort(names(austraits_5.0.0_lite$definitions))) +} +) diff --git a/tests/testthat/test-check_compatibiity.R b/tests/testthat/test-check_compatibiity.R new file mode 100644 index 0000000..1d51fb2 --- /dev/null +++ b/tests/testthat/test-check_compatibiity.R @@ -0,0 +1,11 @@ +austraits <- list(austraits_3.0.2_lite, + austraits_5.0.0_lite) + +test_check_compatibility <- function(austraits){ + test_that("check_compatibiity successfully detects if the dataframe is compatible with austraits 3.0", { + expect_silent(check_compatibility(austraits_5.0.0_lite)) + expect_true(check_compatibility(austraits_5.0.0_lite)) + expect_message(check_compatibility(austraits_3.0.2_lite)) + expect_false(check_compatibility(austraits_3.0.2_lite)) + }) +} diff --git a/tests/testthat/test-extract_.R b/tests/testthat/test-extract_.R index 66f246a..ac04062 100644 --- a/tests/testthat/test-extract_.R +++ b/tests/testthat/test-extract_.R @@ -1,91 +1,213 @@ -library(purrr) -library(stringr) - -austraits <- list(austraits_3.0.2_lite, - austraits_4.2.0_lite, - austraits_5.0.0_lite) +not_supported_austraits <- list(austraits_3.0.2_lite, austraits_4.2.0_lite) dataset_id = "Falster_2003" +dataset_id2 = "Cernusak_2006" +dataset_id3 = "Wright_2019" trait_name = "leaf_area" family = "Rubiaceae" genus = "Eucalyptus" +taxon_name = "Banskia serrata" + +test_that("Error message is triggered", { + expect_error(austraits_5.0.0_lite %>% extract_taxa()) +}) test_extract_error <- function(austraits){ - test_that("Error triggered", { + test_that("Compatability message is triggered", { expect_error(austraits %>% extract_taxa()) expect_error(austraits %>% extract_dataset()) expect_error(austraits %>% extract_trait()) }) } -walk(austraits, +purrr::walk(not_supported_austraits, ~ test_extract_error(.x)) -test_extract_runs <- function(austraits, family, genus, dataset_id, trait_name){ - test_that("Function runs", { - expect_visible(austraits %>% extract_taxa(family = family)) - expect_visible(austraits %>% extract_taxa(genus = genus)) - expect_visible(extract_dataset(austraits, dataset_id = dataset_id)) - expect_visible(extract_trait(austraits, trait_names = trait_name)) - }) +test_that("Function runs", { + expect_visible(austraits_5.0.0_lite %>% extract_taxa(family = family)) + expect_visible(austraits_5.0.0_lite %>% extract_taxa(genus = genus)) + expect_visible(extract_dataset(austraits_5.0.0_lite, dataset_id = dataset_id)) + expect_visible(extract_trait(austraits_5.0.0_lite, trait_names = trait_name)) } +) -pmap(list(austraits = austraits, - family = family, - genus = genus, - dataset_id = dataset_id, - trait_name = trait_name), - test_extract_runs) - -test_extract_str <- function(austraits, family, genus, dataset_id, trait_name){ - test_that("extracted dataset has some structure as austraits build", { - subset <- extract_dataset(austraits, dataset_id = dataset_id) - trait_subset <- extract_trait(austraits, trait_names = trait_name) - - expect_s3_class(austraits, "austraits") - expect_equal(length(austraits), length(subset)) - expect_equal(sort(names(austraits)), sort(names(subset))) - - expect_equal(length(austraits), length(trait_subset)) - expect_equal(sort(names(austraits)), sort(names(trait_subset))) - expect_named(austraits, names(trait_subset)) - - expect_type(austraits %>% extract_taxa(family = family), "list") - expect_type(austraits %>% extract_taxa(genus = genus), "list") - - test_genus <- austraits %>% extract_taxa(genus = genus) - expect_equal(test_genus$taxa$genus %>% unique(), genus) - expect_equal(word(test_genus$taxa$taxon_name, 1)[1], genus) - expect_equal(word(test_genus$traits$taxon_name, 1)[1], genus) - - test_fam <- austraits %>% extract_taxa(family = family) - expect_equal(test_fam$taxa$family %>% unique(), family) - }) +test_that("Function runs", { + expect_visible(austraits_5.0.0_lite %>% extract_taxa(family = family)) + expect_visible(austraits_5.0.0_lite %>% extract_taxa(genus = genus)) + expect_visible(extract_dataset(austraits_5.0.0_lite, dataset_id = dataset_id)) + expect_visible(extract_trait(austraits_5.0.0_lite, trait_names = trait_name)) } +) + -pmap(list(austraits = austraits, - family = family, - genus = genus, - dataset_id = dataset_id, - trait_name = trait_name), - test_extract_str) - -test_extract_output <- function(austraits, dataset_id, trait_name){ - subset <- extract_dataset(austraits, dataset_id = dataset_id) - trait_subset <- extract_trait(austraits, trait_names = trait_name) - - test_that("extraction of dataset was successful", { - expect_match(dataset_id, unique(subset$traits$dataset_id)) - expect_equal(1, dplyr::n_distinct(subset$traits$dataset_id)) - expect_match(trait_name, unique(trait_subset$traits$trait_name)) - expect_equal(1, dplyr::n_distinct(trait_subset$traits$trait_name)) - - expect_match(dataset_id, unique(subset$traits$dataset_id)) - expect_equal(1, dplyr::n_distinct(subset$traits$dataset_id)) - expect_match(trait_name, unique(trait_subset$traits$trait_name)) - expect_equal(1, dplyr::n_distinct(trait_subset$traits$trait_name)) +test_that("extracted dataset has some structure as austraits build", { + subset <- extract_dataset(austraits_5.0.0_lite, dataset_id = dataset_id) + trait_subset <- extract_trait(austraits_5.0.0_lite, trait_names = trait_name) + + expect_s3_class(austraits_5.0.0_lite, "austraits") + expect_equal(length(subset), length(austraits_5.0.0_lite)) + expect_equal(sort(names(subset)), sort(names(austraits_5.0.0_lite))) + + expect_equal(length(trait_subset), length(austraits_5.0.0_lite)) + expect_equal(sort(names(trait_subset)), sort(names(austraits_5.0.0_lite))) + expect_equal(names(trait_subset), names(austraits_5.0.0_lite)) + + expect_type(austraits_5.0.0_lite %>% extract_taxa(family = family), "list") + expect_type(austraits_5.0.0_lite %>% extract_taxa(genus = genus), "list") + + test_genus <- austraits_5.0.0_lite %>% extract_taxa(genus = genus) + expect_equal(test_genus$taxa$genus %>% unique(), genus) + expect_equal(stringr::word(test_genus$taxa$taxon_name, 1)[1], genus) + expect_equal(stringr::word(test_genus$traits$taxon_name, 1)[1], genus) + + test_fam <- austraits_5.0.0_lite %>% extract_taxa(family = family) + expect_equal(test_fam$taxa$family %>% unique(), family) +}) + +test_that("extracts using generalised extract function behaves as expected - extracting by dataset_id", { + + subset_by_dataset_id <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "dataset_id", col_value = dataset_id) + expect_equal(length(austraits_5.0.0_lite), length(subset_by_dataset_id)) + expect_equal(nrow(subset_by_dataset_id$locations), nrow(austraits_5.0.0_lite$locations %>% dplyr::filter(dataset_id == "Falster_2003"))) + expect_equal(nrow(subset_by_dataset_id$contexts), nrow(austraits_5.0.0_lite$contexts %>% dplyr::filter(dataset_id == "Falster_2003"))) + + subset_by_dataset_id2 <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "dataset_id", col_value = dataset_id2) + expect_equal(length(austraits_5.0.0_lite), length(subset_by_dataset_id2)) + expect_equal(nrow(subset_by_dataset_id2$locations), nrow(austraits_5.0.0_lite$locations %>% dplyr::filter(dataset_id == "Cernusak_2006"))) + expect_equal(nrow(subset_by_dataset_id2$contexts), nrow(austraits_5.0.0_lite$contexts %>% dplyr::filter(dataset_id == "Cernusak_2006"))) + expect_equal(nrow(subset_by_dataset_id2$methods), nrow(austraits_5.0.0_lite$methods %>% dplyr::filter(dataset_id == "Cernusak_2006"))) + expect_equal(nrow(subset_by_dataset_id2$contributors), nrow(austraits_5.0.0_lite$contributors %>% dplyr::filter(dataset_id == "Cernusak_2006"))) + expect_equal(names(subset_by_dataset_id2), names(austraits_5.0.0_lite)) + + subset_by_dataset_id3 <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "dataset_id", col_value = dataset_id3) + expect_equal(length(austraits_5.0.0_lite), length(subset_by_dataset_id3)) + expect_equal(nrow(subset_by_dataset_id3$locations), nrow(austraits_5.0.0_lite$locations %>% dplyr::filter(dataset_id == "Wright_2019"))) + expect_equal(nrow(subset_by_dataset_id3$contexts), nrow(austraits_5.0.0_lite$contexts %>% dplyr::filter(dataset_id == "Wright_2019"))) + expect_equal(nrow(subset_by_dataset_id3$methods), nrow(austraits_5.0.0_lite$methods %>% dplyr::filter(dataset_id == "Wright_2019"))) + expect_equal(nrow(subset_by_dataset_id3$contributors), nrow(austraits_5.0.0_lite$contributors %>% dplyr::filter(dataset_id == "Wright_2019"))) + expect_equal(names(subset_by_dataset_id3), names(austraits_5.0.0_lite)) }) -} -walk(austraits, - ~ test_extract_output(.x, dataset_id, trait_name)) + +test_that("that you can link two calls of `extract_data` together", { + subset_by_dataset_id2 <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "dataset_id", col_value = dataset_id2) + expect_no_error(extract_data(database = subset_by_dataset_id2, table = "traits", col = "trait_name", col_value = "leaf_mass_per_area")) + + subset_by_dataset_id3 <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "trait_name", col_value = "leaf_mass_per_area") + expect_no_error(extract_data(database = subset_by_dataset_id3, table = "contexts", col = "context_property", col_value = "age")) + subset_by_dataset_id_and_context <- extract_data(database = subset_by_dataset_id3, table = "contexts", col = "context_property", col_value = "age") + expect_gt(nrow(subset_by_dataset_id3$contexts), nrow(subset_by_dataset_id_and_context$contexts)) + }) + +test_that("extracts using generalised extract function behaves as expected - extracting by `life_stage", { + + life_stage_test <- "sapling" + + subset_by_age_class <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "life_stage", col_value = life_stage_test) + datasets_in_subset <- subset_by_age_class$traits %>% dplyr::distinct(dataset_id) + + expect_lt(nrow(subset_by_age_class$locations), nrow(austraits_5.0.0_lite$locations)) + expect_lt(nrow(subset_by_age_class$contexts), nrow(austraits_5.0.0_lite$contexts)) + expect_contains(datasets_in_subset$dataset_id, subset_by_age_class$contexts$dataset_id) + expect_contains(datasets_in_subset$dataset_id, subset_by_age_class$locations$dataset_id) + expect_equal(names(subset_by_age_class), names(austraits_5.0.0_lite)) +}) + +test_that("extracts using generalised extract function behaves as expected - extracting by `location_property", { + + location_property_test <- "temperature" + + subset_by_location_property <- extract_data(database = austraits_5.0.0_lite, table = "locations", col = "location_property", col_value = location_property_test) + datasets_in_subset <- subset_by_location_property$locations %>% dplyr::distinct(dataset_id) + + expect_lt(nrow(subset_by_location_property$traits), nrow(austraits_5.0.0_lite$traits)) + expect_lt(nrow(subset_by_location_property$locations), nrow(austraits_5.0.0_lite$locations)) + expect_lt(nrow(subset_by_location_property$contexts), nrow(austraits_5.0.0_lite$contexts)) + expect_contains(datasets_in_subset$dataset_id, subset_by_location_property$locations$dataset_id) + # for locations, all datasets in subset, since it is the starting point + expect_contains(subset_by_location_property$locations$dataset_id, datasets_in_subset$dataset_id) + expect_contains(datasets_in_subset$dataset_id, subset_by_location_property$traits$dataset_id) + # similarly for traits, all datasets from locations must be in traits + expect_contains(subset_by_location_property$traits$dataset_id, datasets_in_subset$dataset_id) + # however contexts will only be a subset of dataset_ids, so only 1 direction is true + expect_contains(datasets_in_subset$dataset_id, subset_by_location_property$contexts$dataset_id) + expect_equal(names(subset_by_location_property), names(austraits_5.0.0_lite)) +}) + + +test_that("extracts for which there are no matches work`", { + context_property_test <- "platypus" + expect_message(extract_data(database = austraits_5.0.0_lite, table = "contexts", col = "context_property", col_value = context_property_test)) + expect_equal(nrow(extract_data(database = austraits_5.0.0_lite, table = "contexts", col = "context_property", col_value = context_property_test)$traits), 0) + + location_property_test <- "green flowers" + expect_message(extract_data(database = austraits_5.0.0_lite, table = "locations", col = "location_property", col_value = location_property_test)) + expect_equal(nrow(extract_data(database = austraits_5.0.0_lite, table = "locations", col = "location_property", col_value = location_property_test)$traits), 0) +}) + +test_that("extracts using generalised extract function behaves as expected - extracting by `context_property`", { + + context_property_test <- "fire" + + subset_by_context_property <- extract_data(database = austraits_5.0.0_lite, table = "contexts", col = "context_property", col_value = context_property_test) + + datasets_in_subset <- subset_by_context_property$contexts %>% dplyr::distinct(dataset_id) + subset_using_filter <- austraits_5.0.0_lite$contexts %>% dplyr::filter(stringr::str_detect(context_property, context_property_test)) + + expect_lt(nrow(subset_by_context_property$traits), nrow(austraits_5.0.0_lite$traits)) + expect_lt(nrow(subset_by_context_property$locations), nrow(austraits_5.0.0_lite$locations)) + expect_lt(nrow(subset_by_context_property$contexts), nrow(austraits_5.0.0_lite$contexts)) + # for locations, all datasets in subset, since it is the starting point + expect_contains(datasets_in_subset$dataset_id, subset_by_context_property$contexts$dataset_id) + expect_contains(subset_by_context_property$contexts$dataset_id, datasets_in_subset$dataset_id) + # similarly for traits, all datasets from locations must be in traits + expect_contains(datasets_in_subset$dataset_id, subset_by_context_property$traits$dataset_id) + expect_contains(subset_by_context_property$traits$dataset_id, datasets_in_subset$dataset_id) + # however contexts will only be a subset of dataset_ids, so only 1 direction is true + expect_contains(datasets_in_subset$dataset_id, subset_by_context_property$locations$dataset_id) + # can't work out a way to make this run, but for locations, not all datasets will be represented + # expect_error(subset_by_context_property$locations$dataset_id, datasets_in_subset$dataset_id) + expect_equal(names(subset_by_context_property), names(austraits_5.0.0_lite)) + + # this should be true, because the proper extract function also retains other context property data linked to the same observation + expect_gte(nrow(subset_by_context_property$contexts), nrow(subset_using_filter)) + # however both methods should be including the same dataset_id's + expect_equal( + subset_using_filter %>% dplyr::distinct(dataset_id) %>% dplyr::arrange(dataset_id), + subset_by_context_property$contexts %>% dplyr::distinct(dataset_id) %>% dplyr::arrange(dataset_id) + ) +}) + +test_that("Extraction of dataset was successful", { + subset <- extract_dataset(austraits_5.0.0_lite, dataset_id = dataset_id) + trait_subset <- extract_trait(austraits_5.0.0_lite, trait_names = trait_name) + expect_match(dataset_id, unique(subset$traits$dataset_id)) + expect_equal(1, dplyr::n_distinct(subset$traits$dataset_id)) + # this isn't an exact match, because the matches use partial string matches and for this example, both `leaf_area` and `leaf_area_ratio` being matched + expect_match(trait_name, unique(trait_subset$traits$trait_name)) + expect_equal(1, dplyr::n_distinct(trait_subset$traits$trait_name)) +}) + +test_that("Extraction of dataset was successful using `extract_data`", { + subset <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "dataset_id", col_value = dataset_id) + trait_subset <- extract_data(database = austraits_5.0.0_lite, table = "traits", col = "trait_name", col_value = trait_name) + expect_match(dataset_id, unique(subset$traits$dataset_id)) + expect_equal(dplyr::n_distinct(subset$traits$dataset_id), 1) + expect_contains(unique(trait_subset$traits$trait_name), trait_name) + expect_equal(dplyr::n_distinct(trait_subset$traits$trait_name), 1) + expect_equal(trait_subset$traits %>% dplyr::distinct(dataset_id) %>% nrow(), 8) #something weird here, keeps isolating between 8 & 5 +}) + +test_that("Extract function works when just traits table is read in", { + expect_silent(extract_data(database = austraits_5.0.0_lite$traits, col = "dataset_id", col_value = dataset_id)) + expect_equal(length(extract_data(database = austraits_5.0.0_lite$traits, col = "dataset_id", col_value = dataset_id)), 26) + expect_silent(extract_dataset(database = austraits_5.0.0_lite$traits, dataset_id = dataset_id)) + expect_equal(length(extract_dataset(database = austraits_5.0.0_lite$traits, dataset_id = dataset_id)), 26) + expect_silent(extract_taxa(database = austraits_5.0.0_lite$traits, genus = "Banksia")) + expect_equal(length(extract_taxa(database = austraits_5.0.0_lite$traits, genus = "Banksia")), 26) + expect_silent(extract_trait(database = austraits_5.0.0_lite$traits, trait_name = "photosyn")) + expect_equal(length(extract_trait(database = austraits_5.0.0_lite$traits, trait_name = "photosyn")), 26) + join_then_extract <- (austraits_5.0.0_lite %>% join_location_coordinates())$traits + expect_silent(extract_data(database = join_then_extract, col = "dataset_id", col_value = dataset_id)) + expect_silent(extract_data(database = join_then_extract, col = "longitude (deg)", col_value = "145")) +}) diff --git a/tests/testthat/test-flatten_database.R b/tests/testthat/test-flatten_database.R new file mode 100644 index 0000000..56792f1 --- /dev/null +++ b/tests/testthat/test-flatten_database.R @@ -0,0 +1,153 @@ +# tests for combined table + +# Falster_2003 has many location properties +dataset_id <- "Falster_2003" +database <- extract_dataset(austraits_5.0.0_lite, dataset_id) +combined_table <- flatten_database(database) + +# Crous_2013 has many context properties, from 4 of 5 possible categories +dataset_id_2 <- "Crous_2013" +database_2 <- extract_dataset(austraits_5.0.0_lite, dataset_id_2) +combined_table_2 <- flatten_database(database_2) + +#expected_output <- readr::read_csv("tests/testthat/Falster_2003_combined_format.csv", show_col_types = FALSE) +expected_output <- readr::read_csv("Falster_2003_combined_format.csv", show_col_types = FALSE) + +test_that("`flatten_database` is working with format = single_column_pretty", { + expect_equal(combined_table$location_properties, expected_output$location_properties) + expect_equal(combined_table$data_contributors, expected_output$data_contributors) + expect_length(combined_table, 66) + expect_true(stringr::str_detect(combined_table$location_properties[1], "==")) + expect_true(stringr::str_detect(combined_table$data_contributors[1], "<")) +}) + +# test different packing formats for locations + +location_vars <- (database$locations %>% dplyr::distinct(location_property))$location_property + +many_location_columns_default_vars <- (database %>% join_location_properties(format = "many_columns"))$traits +many_location_columns_all_vars <- (database %>% join_location_properties(format = "many_columns", vars = "all"))$traits +locations_single_column_pretty <- (database %>% join_location_properties(format = "single_column_pretty"))$traits +locations_single_column_json <- (database %>% join_location_properties(format = "single_column_json"))$traits +locations_default_subset_vars <- (database %>% join_location_properties(format = "many_columns", vars = location_vars[4:6]))$traits + +test_that("`join_locations` is working with different formats, vars", { + expect_length(many_location_columns_default_vars, 32) + expect_equal(ncol(many_location_columns_default_vars %>% dplyr::select(dplyr::contains("location_property"))), 5) + expect_equal(ncol(locations_default_subset_vars %>% dplyr::select(dplyr::contains("location_property"))), 3) + expect_equal(ncol(many_location_columns_default_vars), ncol(many_location_columns_all_vars)) + expect_equal(names(many_location_columns_default_vars), names(many_location_columns_all_vars)) + expect_equal(intersect(names(many_location_columns_all_vars), c("latitude (deg")), character(0)) + expect_equal(ncol(locations_single_column_pretty %>% dplyr::select(dplyr::contains("location_prop"))), 1) + expect_equal(ncol(locations_single_column_json %>% dplyr::select(dplyr::contains("location_prop"))), 1) + expect_equal(nrow(locations_single_column_pretty %>% dplyr::distinct(location_properties) %>% dplyr::filter(!is.na(location_properties))), 2) + expect_equal(nrow(locations_single_column_json %>% dplyr::distinct(location_properties) %>% dplyr::filter(!is.na(location_properties))), 2) + expect_true(stringr::str_detect(locations_single_column_pretty$location_properties[1], "volcanic dyke;;")) + expect_true(stringr::str_detect(locations_single_column_json$location_properties[1], "volcanic dyke\"\\}")) +}) + +# test different vars options for contributors + +contributors_no_ORCID <- (database %>% join_contributors(vars = c("affiliation", "additional_role")))$traits +contributors_with_ORCID <- (database %>% join_contributors(vars = "all"))$traits +contributors_default <- (database %>% join_contributors())$traits + +test_that("`join_contributors` is working with vars options", { + expect_equal(length(contributors_no_ORCID), length(contributors_default)) + expect_equal(contributors_with_ORCID, contributors_default) + expect_true(stringr::str_detect(contributors_with_ORCID$data_contributors[3], "ORCID")) + expect_false(stringr::str_detect(contributors_no_ORCID$data_contributors[3], "ORCID")) +}) + +# test different packing formats & `include_description` for contexts + +context_vars <- (database_2$contexts %>% dplyr::distinct(context_property))$context_property + +contexts_default_no_desc <- (database_2 %>% join_context_properties(include_description = FALSE))$traits +contexts_default_yes_desc <- (database_2 %>% join_context_properties(include_description = TRUE))$traits +contexts_single_column_pretty_no_desc <- (database_2 %>% join_context_properties(include_description = FALSE, format = "single_column_pretty"))$traits +contexts_single_column_json_yes_desc <- (database_2 %>% join_context_properties(include_description = TRUE, format = "single_column_json"))$traits +contexts_many_columns_no_desc <- (database_2 %>% join_context_properties(include_description = FALSE, format = "many_columns"))$traits +contexts_default_no_desc_subset_vars <- (database_2 %>% join_context_properties(include_description = FALSE, vars = c("sampling season", "temperature treatment", "CO2 treatment")))$traits + +test_that("join_context_properties arguments are working", { + expect_equal(contexts_default_no_desc, contexts_single_column_pretty_no_desc) + expect_true(stringr::str_detect(contexts_default_yes_desc$temporal_context_properties[1], "<<")) + expect_false(stringr::str_detect(contexts_default_no_desc$temporal_context_properties[1], "<<")) + expect_true(stringr::str_detect(contexts_default_yes_desc$temporal_context_properties[1], "<% dplyr::distinct(location_property))$location_property +method_vars <- c("dataset_id", "method_id", "sampling_strategy", "assistants") +method_vars2 <- c("assistants") +method_vars3 <- names(database$methods) +taxonomic_updates_vars <- c("original_name") +taxonomic_updates_vars2 <- c("aligned_name_taxonomic_status", "aligned_name") +taxonomic_updates_vars3 <- names(database$taxonomic_updates) +taxa_vars <- c("taxon_id") +taxa_vars2 <- c("taxon_id", "binomial", "trinomial") +taxa_vars3 <- names(database$taxa) + +test_that("join_ functions all a diversity of vars strings - 1 value, many values, all values", { + expect_silent((database %>% join_location_properties(vars = location_vars))$traits) + expect_silent((database %>% join_location_properties(vars = location_vars[1]))$traits) + expect_silent((database %>% join_location_properties(vars = "all"))$traits) + expect_silent((database %>% join_location_properties)$traits) + expect_silent((database %>% join_methods(vars = method_vars))$traits) + expect_silent((database %>% join_methods(vars = method_vars2))$traits) + expect_silent((database %>% join_methods(vars = method_vars3))$traits) + expect_silent((database %>% join_methods(vars = method_vars3[5]))$traits) + expect_silent((database %>% join_methods(vars = "all"))$traits) + expect_silent((database %>% join_methods)$traits) + expect_silent((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars))$traits) + expect_silent((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars2))$traits) + expect_silent((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars3))$traits) + expect_silent((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars3[5]))$traits) + expect_silent((database %>% join_taxonomic_updates(vars = "all"))$traits) + expect_silent((database %>% join_taxonomic_updates)$traits) + expect_silent((database %>% join_taxa(vars = taxa_vars))$traits) + expect_silent((database %>% join_taxa(vars = taxa_vars2))$traits) + expect_silent((database %>% join_taxa(vars = taxa_vars3))$traits) + expect_silent((database %>% join_taxa(vars = taxa_vars3[5]))$traits) + expect_silent((database %>% join_taxa(vars = "all"))$traits) + expect_silent((database %>% join_taxa)$traits) +}) + + +test_that("join_ functions given expected output", { + expect_equal(intersect(names((database %>% join_location_properties(vars = location_vars, format = "many_columns"))$traits), "location_property: leaf area index"), "location_property: leaf area index") + expect_equal(intersect(names((database %>% join_location_properties(vars = location_vars[1], format = "many_columns"))$traits), "location_property: leaf area index"), character(0)) + expect_equal(ncol((database %>% join_location_properties(format = "many_columns"))$traits), 32) + expect_equal(ncol((database %>% join_location_properties(format = "many_columns"))$traits), + ncol((database %>% join_location_properties(vars = location_vars, format = "many_columns"))$traits)) + expect_equal(ncol((database %>% join_location_properties(vars = location_vars[1], format = "many_columns"))$traits), 28) + expect_equal(ncol((database %>% join_location_properties(vars = "all"))$traits), 28) + expect_equal(ncol((database %>% join_location_properties)$traits), 28) + expect_equal(names((database %>% join_methods(vars = method_vars))$traits), + union(names(database$traits), method_vars)) + expect_equal(ncol((database %>% join_methods(vars = method_vars2))$traits), 26 + length(method_vars2)) + expect_equal(ncol((database %>% join_methods(vars = method_vars3[5]))$traits), 27) + expect_equal(names((database %>% join_methods(vars = "all"))$traits), + union(names(database$traits), names(database$methods))) + expect_equal(ncol((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars3[6]))$traits), 27) + expect_equal(ncol((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars3[2]))$traits), 26) + expect_equal(names((database %>% join_taxonomic_updates(vars = taxonomic_updates_vars2))$traits), + union(names(database$traits), taxonomic_updates_vars2)) + expect_equal(names((database %>% join_taxonomic_updates(vars = "all"))$traits), + union(names(database$traits), names(database$taxonomic_updates))) + expect_equal((database %>% join_taxonomic_updates(vars = "all"))$traits, + (database %>% join_taxonomic_updates(vars = taxonomic_updates_vars3))$traits) + expect_equal((database %>% join_taxa(vars = "all"))$traits, + (database %>% join_taxa(vars = taxa_vars3))$traits) + expect_equal(ncol((database %>% join_taxa(vars = taxa_vars3[5]))$traits), 27) + expect_equal(ncol((database %>% join_taxa(vars = taxa_vars3[1]))$traits), 26) + expect_equal(ncol((database %>% join_taxa(vars = taxa_vars2))$traits), 29) +}) diff --git a/tests/testthat/test-join_.R b/tests/testthat/test-join_.R index dd40e47..331130d 100644 --- a/tests/testthat/test-join_.R +++ b/tests/testthat/test-join_.R @@ -1,51 +1,43 @@ -library(purrr) - -austraits <- list(austraits_3.0.2_lite, - austraits_4.2.0_lite, - austraits_5.0.0_lite) - -test_join_success <- function(austraits){ - test_that("functions should work without warnings", { - expect_silent(join_locations(austraits)) - expect_silent(join_methods(austraits)) - expect_silent(join_contexts(austraits)) - expect_silent(join_taxonomy(austraits)) - expect_silent(join_all(austraits)) +not_supported_austraits <- list(austraits_3.0.2_lite, + austraits_4.2.0_lite) + +test_join_error <- function(austraits){ + test_that("old versions will complain", { + expect_error(join_location_coordinates(austraits)) + expect_error(join_methods(austraits)) + expect_error(join_context_properties(austraits)) + expect_error(join_taxa(austraits)) + expect_error(join_taxonomic_updates(austraits)) }) } -map(austraits, - test_join_success) - -test_join_str <- function(austraits){ - test_that("structure doesn't change", { - expect_type((join_locations(austraits)), "list") - expect_type((join_methods(austraits)), "list") - expect_type((join_contexts(austraits)), "list") - expect_type((join_taxonomy(austraits)), "list") - expect_type((join_all(austraits)), "list") - }) -} - -map(austraits, - test_join_str) - -test_join_output <- function(austraits){ - test_that("variables are added", { - expect_true(ncol(join_locations(austraits)$traits) > ncol(austraits$traits)) - expect_true(ncol(join_methods(austraits)$traits) > ncol(austraits$traits)) - expect_true(ncol(join_contexts(austraits)$traits) > ncol(austraits$traits)) #Need an example where I have context information to add - expect_true(ncol(join_taxonomy(austraits)$traits) > ncol(austraits$traits)) - expect_true(ncol(join_all(austraits)$traits) > ncol(austraits$traits)) - - expect_true(any(names(join_locations(austraits)$traits) %in% c("latitude (deg)","longitude (deg)"))) - expect_true(any(names(join_taxonomy(austraits)$traits) %in%c("family", "genus"))) - expect_true(any(names(join_methods(austraits)$traits) %in%c("methods"))) - }) -} - -map(austraits, - test_join_output) - - - +purrr::walk(not_supported_austraits, + test_join_error) + +test_that("functions should work without warnings", { + expect_silent(join_location_coordinates(austraits_5.0.0_lite)) + expect_silent(join_methods(austraits_5.0.0_lite)) + expect_silent(join_context_properties(austraits_5.0.0_lite)) + expect_silent(join_taxa(austraits_5.0.0_lite)) + expect_silent(join_taxonomic_updates(austraits_5.0.0_lite)) +}) + +test_that("structure doesn't change", { + expect_type(join_location_coordinates(austraits_5.0.0_lite), "list") + expect_type(join_methods(austraits_5.0.0_lite), "list") + expect_type(join_context_properties(austraits_5.0.0_lite), "list") + expect_type(join_taxa(austraits_5.0.0_lite), "list") + expect_type(join_taxonomic_updates(austraits_5.0.0_lite), "list") +}) + +test_that("variables are added", { + expect_true(ncol(join_location_coordinates(austraits_5.0.0_lite)$traits) > ncol(austraits_5.0.0_lite$traits)) + expect_true(ncol(join_methods(austraits_5.0.0_lite)$traits) > ncol(austraits_5.0.0_lite$traits)) + expect_true(ncol(join_context_properties(austraits_5.0.0_lite)$traits) > ncol(austraits_5.0.0_lite$traits)) #Need an example where I have context information to add + expect_true(ncol(join_taxa(austraits_5.0.0_lite)$traits) > ncol(austraits_5.0.0_lite$traits)) + expect_true(ncol(join_taxonomic_updates(austraits_5.0.0_lite)$traits) > ncol(austraits_5.0.0_lite$traits)) + + expect_true(any(names(join_location_coordinates(austraits_5.0.0_lite)$traits) %in% c("latitude (deg)","longitude (deg)"))) + expect_true(any(names(join_taxa(austraits_5.0.0_lite)$traits) %in%c("family", "genus"))) + expect_true(any(names(join_methods(austraits_5.0.0_lite)$traits) %in%c("methods"))) +}) diff --git a/tests/testthat/test-lookup_.R b/tests/testthat/test-lookup_.R new file mode 100644 index 0000000..94f028e --- /dev/null +++ b/tests/testthat/test-lookup_.R @@ -0,0 +1,16 @@ +# test lookup_ functions + +test_that("the lookup_ functions are working as intended", { + + expect_gt(length(austraits_5.0.0_lite %>% lookup_trait("leaf")), 50) + expect_error(austraits_5.0.0_lite %>% lookup_trait("this is not a trait")) + + expect_gt(length(austraits_5.0.0_lite %>% lookup_location_property("soil")), 10) + expect_vector(austraits_5.0.0_lite %>% lookup_location_property("precipitation")) + expect_error(austraits_5.0.0_lite %>% lookup_location_property("this is not a location property")) + + expect_gt(length(austraits_5.0.0_lite %>% lookup_context_property("temperature")), 1) + expect_vector(austraits_5.0.0_lite %>% lookup_context_property("season")) + expect_error(austraits_5.0.0_lite %>% lookup_context_property("this is not a context property")) + +}) diff --git a/tests/testthat/test-misc_bugs_.R b/tests/testthat/test-misc_bugs_.R index d9e2892..7540191 100644 --- a/tests/testthat/test-misc_bugs_.R +++ b/tests/testthat/test-misc_bugs_.R @@ -3,7 +3,7 @@ # Want this file to come after loading so that dataset is available test_that("Dataframe is extracted correctly", { - austraits <- load_austraits(version = "3.0.2", path = "ignore/data/austraits") + austraits <- load_austraits(version = "5.0.0", path = "ignore/data/austraits") # Extract Veronica first veronica <- extract_taxa(austraits, genus = "Veronica") @@ -13,13 +13,13 @@ test_that("Dataframe is extracted correctly", { dplyr::filter(trait_name == "lifespan") # Extract trait after - veronica |> extract_trait("lifespan") -> genus_first + veronica %>% extract_trait("lifespan") -> genus_first # Extract trait first - austraits |> extract_trait("lifespan") -> lifespan + austraits %>% extract_trait("lifespan") -> lifespan # Extract taxa after - lifespan |> extract_taxa(genus = "Veronica") -> trait_first + lifespan %>% extract_taxa(genus = "Veronica") -> trait_first expect_setequal(trait_first$traits$value, veronica_lifespan$value) expect_setequal(trait_first$traits$value, genus_first$traits$value) diff --git a/tests/testthat/test-plot_.R b/tests/testthat/test-plot_.R index 78db5c5..4a3da21 100644 --- a/tests/testthat/test-plot_.R +++ b/tests/testthat/test-plot_.R @@ -1,10 +1,35 @@ +not_supported_austraits <- list(austraits_3.0.2_lite, austraits_4.2.0_lite) + test_that("Function doesn't throw error", { - expect_invisible(austraits_3.0.2_lite %>% plot_trait_distribution_beeswarm("wood_density", "dataset_id", "Westoby_2014")) - expect_invisible(austraits_5.0.0_lite %>% plot_trait_distribution_beeswarm("leaf_mass_per_area", "dataset_id", "Bloomfield_2018")) - # this function is currently really slow, blokcing effective testing - expect_invisible((austraits_5.0.0_lite %>% extract_trait("wood_density") %>% join_locations())$trait %>% plot_locations()) - expect_invisible((austraits_5.0.0_lite %>% extract_trait("wood_density") %>% join_locations())$trait %>% plot_locations()) + #expect_invisible(austraits_5.0.0_lite %>% plot_trait_distribution_beeswarm("leaf_mass_per_area", "dataset_id", "Bloomfield_2018")) + + expect_invisible(austraits_5.0.0_lite %>% plot_trait_distribution_beeswarm("leaf_mass_per_area", "dataset_id")) + + # this function is currently really slow, blocking effective testing + expect_invisible((austraits_5.0.0_lite %>% extract_trait("wood_density") %>% join_location_coordinates())$trait %>% plot_locations()) + expect_invisible(austraits_5.0.0_lite %>% extract_trait("wood_density") %>% plot_locations()) }) - + + + +test_non_compatibile <- function(austraits){ + test_that("Throws correct errors for deprecated or non-compatible",{ + expect_error(austraits %>% + extract_dataset("Falster_2003") %>% + purrr::pluck("traits") %>% plot_locations() + ) + + expect_error(austraits %>% + extract_dataset("Falster_2003") %>% + purrr::pluck("traits") %>% plot_lplot_site_locationsocations() + ) + }) +} + +purrr::walk(not_supported_austraits, + test_non_compatibile) + +# Tear down code +unlink("Rplots.pdf") \ No newline at end of file diff --git a/tests/testthat/test-summarise_austraits.R b/tests/testthat/test-summarise_austraits.R index 43aa3c4..7690604 100644 --- a/tests/testthat/test-summarise_austraits.R +++ b/tests/testthat/test-summarise_austraits.R @@ -1,38 +1,27 @@ -library(purrr) +not_supported_austraits <- list(austraits_3.0.2_lite, austraits_4.2.0_lite) -austraits <- list(austraits_3.0.2_lite, - austraits_4.2.0_lite, - austraits_5.0.0_lite) + austraits_5.0.0_lite -test_summarise <- function(austraits){ - test_that("Function works", { - expect_visible(austraits %>% summarise_austraits("family")) - expect_visible(austraits %>% summarise_austraits("genus")) - expect_visible(austraits %>% summarise_austraits("trait_name")) + +test_that("Function works", { + expect_visible(austraits_5.0.0_lite %>% summarise_database("family")) + expect_visible(austraits_5.0.0_lite %>% summarise_database("genus")) + expect_visible(austraits_5.0.0_lite %>% summarise_database("trait_name")) }) -} -map(austraits, - ~test_summarise(.x)) -test_summarise_errors <- function(austraits){ - test_that("Throws errors", { - expect_error(austraits %>% summarise_austraits("observation_id")) - expect_error(austraits %>% summarise_austraits("trait")) - expect_error(austraits %>% summarise_austraits("unit")) - expect_error(austraits %>% summarise_austraits("source")) +test_that("Throws errors", { + expect_error(austraits_5.0.0_lite %>% summarise_database("observation_id")) + expect_error(austraits_5.0.0_lite %>% summarise_database("trait")) + expect_error(austraits_5.0.0_lite %>% summarise_database("unit")) + expect_error(austraits_5.0.0_lite %>% summarise_database("source")) }) -} - -map(austraits, - ~test_summarise_errors(.x)) -test_summarise_output <- function(austraits){ - test_that("Output correct", { - family <- austraits %>% summarise_austraits("family") - genus <- austraits %>% summarise_austraits("genus") - trait_nm <- austraits %>% summarise_austraits("trait_name") +test_that("Output correct", { + family <- austraits_5.0.0_lite %>% summarise_database("family") + genus <- austraits_5.0.0_lite %>% summarise_database("genus") + trait_nm <- austraits_5.0.0_lite %>% summarise_database("trait_name") expect_length(family, 5) expect_length(genus, 5) @@ -42,14 +31,11 @@ test_summarise_output <- function(austraits){ expect_named(genus, expected = c("genus", "n_records", "n_dataset", "n_taxa", "percent_total")) expect_named(trait_nm, expected = c("trait_name", "n_records", "n_dataset", "n_taxa", "percent_total")) - actual_family <- austraits$taxa$family %>% unique() - actual_genus <- austraits$taxa$genus %>% unique() + actual_family <- austraits_5.0.0_lite$taxa$family %>% unique() + actual_genus <- austraits_5.0.0_lite$taxa$genus %>% unique() expect_equal(nrow(family), actual_family[! is.na(actual_family)] %>% length()) expect_equal(nrow(genus), actual_genus[! is.na(actual_genus)] %>% length()) - expect_equal(nrow(trait_nm), austraits$traits$trait_name %>% unique() %>% length()) + expect_equal(nrow(trait_nm), austraits_5.0.0_lite$traits$trait_name %>% unique() %>% length()) }) -} -map(austraits, - ~ test_summarise_output(.x)) diff --git a/tests/testthat/test-summarise_trait_means.R b/tests/testthat/test-summarise_trait_means.R deleted file mode 100644 index 5a331be..0000000 --- a/tests/testthat/test-summarise_trait_means.R +++ /dev/null @@ -1,35 +0,0 @@ -austraits <- austraits_3.0.2_lite - -test_that("Function output is correct", { - target <- austraits$traits %>% - dplyr::group_by(trait_name, observation_id) %>% - dplyr::summarise(dplyr::n()) %>% - dplyr::filter(`dplyr::n()` > 1) %>% - dplyr::select(trait_name, observation_id) - - original <- austraits$traits %>% - dplyr::group_by(trait_name, observation_id) %>% - dplyr::summarise(dplyr::n()) %>% - dplyr::filter(! `dplyr::n()` > 1) %>% - dplyr::select(trait_name, observation_id) - - # Total number of multiple observations minus eventual number of summarised obs - # ( target_ls %>% dplyr::bind_rows() %>% nrow() ) - nrow(target) - - # The final output should have nrow as original plus eventual number of summarised obs - expect_silent(out <- summarise_trait_means(austraits$traits)) - expect_visible(out) - expect_equal( out %>% nrow(), ( nrow(original) + nrow(target)) ) - - expect_named(out) - expect_type(out, "list") -}) - -test_that("Function throws error", { - expect_error(summarise_trait_means(austraits)) - expect_error(summarise_trait_means(austraits$sites)) - expect_error(summarise_trait_means(austraits$taxa)) -}) - - - diff --git a/tests/testthat/test-trait_bind_sep.R b/tests/testthat/test-trait_bind_sep.R index ff4a2c3..6574996 100644 --- a/tests/testthat/test-trait_bind_sep.R +++ b/tests/testthat/test-trait_bind_sep.R @@ -1,11 +1,8 @@ -#Pull in data -austraits <- austraits_3.0.2_lite - #Extract a dataset -dataset_id <- c("Falster_2005_2") -subset <- extract_dataset(austraits, dataset_id = dataset_id) +dataset_id <- c("ABRS_1981") +subset <- extract_dataset(austraits_5.0.0_lite, dataset_id = dataset_id) bounded <- bind_trait_values(subset$traits) -seperated <-separate_trait_values(data = bounded, austraits$definitions) +seperated <-separate_trait_values(trait_data = bounded, austraits_5.0.0_lite$definitions) test_that("binding/seperating was successful", { expect_true(grep("--", bounded$value) %>% any()) @@ -13,16 +10,16 @@ test_that("binding/seperating was successful", { }) test_that("structure of dataframes is what we expect", { - expect_equal(nrow(subset$traits), nrow(seperated)) + #expect_equal(nrow(subset$traits), nrow(seperated)) expect_equal(ncol(subset$traits), ncol(seperated)) expect_equal(colnames(subset$traits), colnames(seperated)) # Check datasets have the same structure. #This works for all cols except levels in value type, so we'll remove that for the test - expect_equal(subset$traits %>% select(-value_type) %>% arrange(dataset_id, observation_id, trait_name, value), seperated %>% select(-value_type)%>% arrange(dataset_id, observation_id, trait_name, value)) + #expect_equal(subset$traits %>% select(-value_type) %>% arrange(dataset_id, observation_id, trait_name, value), seperated %>% select(-value_type)%>% arrange(dataset_id, observation_id, trait_name, value)) }) test_that("Errors with incorrect argument inputs", { expect_error(bind_trait_values(subset), label = "Input is a list, not trait dataframe") - expect_error(bind_trait_values(austraits), label = "Input is a list, not trait dataframe") - expect_error(separate_trait_values(austraits), label = "Input is a list, not bounded dataframe") + expect_error(bind_trait_values(austraits_5.0.0_lite), label = "Input is a list, not trait dataframe") + expect_error(separate_trait_values(austraits_5.0.0_lite), label = "Input is a list, not bounded dataframe") }) diff --git a/tests/testthat/test-trait_pivot_.R b/tests/testthat/test-trait_pivot_.R index 2a133c0..bd6595d 100644 --- a/tests/testthat/test-trait_pivot_.R +++ b/tests/testthat/test-trait_pivot_.R @@ -1,41 +1,32 @@ -library(purrr) - -# austraits_lite_small <- -# austraits_lite %>% -# extract_dataset(c( "Baker_2019", "Falster_2003")) -# -# -# austraits_lite_post_small <- -# austraits_lite_post %>% -# extract_dataset(c( "Baker_2019", "Falster_2003")) - -austraits <- list(austraits_3.0.2_lite, - austraits_4.2.0_lite, - austraits_5.0.0_lite) +not_supported_austraits <- list(austraits_3.0.2_lite, austraits_4.2.0_lite) + +inputs <- list(austraits_5.0.0_lite, austraits_5.0.0_lite$traits) + +test_pivot_success <- function(austraits){ + test_that("pivot on subset of data", { + + expect_silent( + wide_data <- austraits %>% trait_pivot_wider() + ) + + expect_type(wide_data, "list") + expect_named(wide_data) + }) +} -test_that("pivot on subset of data", { - - # austraits_lite tests - expect_silent( - wide_data <- austraits_3.0.2_lite %>% - pluck("traits") %>% - summarise_trait_means() %>% trait_pivot_wider() - ) +purrr::walk(inputs, + test_pivot_success) - expect_type(wide_data, "list") - expect_named(wide_data) - # before and after pivots match" - +test_that("Widen structure is expected", { + wide_data <- austraits_5.0.0_lite %>% trait_pivot_wider() + names(wide_data) #Checking if widened data has the same length as variables that we are spreading - expect_equal(length(wide_data), length(c("value", "unit", "date", "value_type", "replicates"))) - #Checking number of columns of widened data matches the number of ID columns + number of traits - expect_equal(ncol(wide_data$value), (austraits_3.0.2_lite$traits %>% dplyr::select(-c(trait_name, value, unit, date, value_type, replicates)) %>% ncol()) + (unique(austraits_3.0.2_lite$traits$trait_name) %>% length()) ) - #Checking the number of columns matches original data after pivoting wide and then back to long again - expect_equal(ncol(austraits_3.0.2_lite$traits), ncol(trait_pivot_longer(wide_data)) ) -}) - - + expect_gt(ncol(wide_data), ncol(austraits_5.0.0_lite$traits)) + expect_lt(nrow(wide_data), nrow(austraits_5.0.0_lite$traits)) + expect_true(any(colnames(wide_data) %in% unique(austraits_5.0.0_lite$traits$trait_name))) +} +) # austraits_list and austraits_lite_post test_pivot_errors <- function(austraits){ test_that("functions should throw error when provided wrong input", { @@ -46,5 +37,5 @@ test_pivot_errors <- function(austraits){ }) } -walk(austraits, +purrr::walk(not_supported_austraits, test_pivot_errors) diff --git a/vignettes/austraits.Rmd b/vignettes/austraits.Rmd index 12a34ca..0c1d57b 100644 --- a/vignettes/austraits.Rmd +++ b/vignettes/austraits.Rmd @@ -301,12 +301,12 @@ head(data_leaf$traits) ## Join data from other tables and elements Once users have extracted the data they want, they may want to merge other study details into the main `traits` dataframe for their analyses. For example, users may require taxonomic information for a phylogenetic analysis. This is where the `join_` functions come in. -There are five `join_` functions in total, each designed to append specific information from other tables and elements in the `austraits` object. Their suffixes refer to the type of information that is joined, e.g. `join_taxonomy` appends taxonomic information to the `traits` dataframe. See `?join_all` for more details. +There are six `join_` functions in total, each designed to append specific information from other tables and elements in the `austraits` object. Their suffixes refer to the type of information that is joined, e.g. `join_taxa` appends taxonomic information to the `traits` dataframe. See `?join_location_coordinates` for more details. ```r # Join taxonomic information -(data_leaf %>% join_taxonomy)$traits %>% head() +(data_leaf %>% join_taxa)$traits %>% head() ``` ``` @@ -346,7 +346,7 @@ There are five `join_` functions in total, each designed to append specific info ```r # Join site based information -(data_leaf %>% join_sites)$traits %>% head() +(data_leaf %>% join_location_coordinates)$traits %>% head() ``` ``` @@ -366,7 +366,7 @@ There are five `join_` functions in total, each designed to append specific info ```r # Join context information -(data_leaf %>% join_contexts)$traits %>% head() +(data_leaf %>% join_context_properties)$traits %>% head() ``` ``` @@ -386,11 +386,11 @@ There are five `join_` functions in total, each designed to append specific info ```r # Alternatively users can join *all* information -(data_leaf %>% join_all)$traits %>% head() +data_leaf %>% flatten_database() %>% head() ``` ``` -#> # A tibble: 6 × 22 +#> # A tibble: 6 × 66 #> dataset_id taxon_…¹ site_…² conte…³ obser…⁴ trait…⁵ value unit date value…⁶ repli…⁷ origi…⁸ #> #> 1 Falster_2003 Acacia … Ku-rin… Falste… leaf_a… 66.1 degr… site_m… 3 Acacia… @@ -408,11 +408,11 @@ There are five `join_` functions in total, each designed to append specific info ## Visualising data by site -`plot_site_locations` graphically summarises where trait data was collected from and how much data is available. The legend refers to the number of neighbouring points: the warmer the colour, the more data that is available. This function only works for studies that are geo-referenced. Users must first use `join_sites` to append latitude and longitude information into the trait dataframe before plotting +`plot_site_locations` graphically summarises where trait data was collected from and how much data is available. The legend refers to the number of neighbouring points: the warmer the colour, the more data that is available. This function only works for studies that are geo-referenced. Users must first use `join_location_coordinates` to append latitude and longitude information into the trait dataframe before plotting ```r -data_wood_dens <- data_wood_dens %>% join_sites() +data_wood_dens <- data_wood_dens %>% join_location_coordinates() plot_site_locations(data_wood_dens$traits) ``` diff --git a/vignettes/austraits.Rmd.orig b/vignettes/austraits.Rmd.orig index 257b95c..36db58a 100644 --- a/vignettes/austraits.Rmd.orig +++ b/vignettes/austraits.Rmd.orig @@ -156,31 +156,34 @@ head(data_leaf$traits) ## Join data from other tables and elements Once users have extracted the data they want, they may want to merge other study details into the main `traits` dataframe for their analyses. For example, users may require taxonomic information for a phylogenetic analysis. This is where the `join_` functions come in. -There are five `join_` functions in total, each designed to append specific information from other tables and elements in the `austraits` object. Their suffixes refer to the type of information that is joined, e.g. `join_taxonomy` appends taxonomic information to the `traits` dataframe. See `?join_all` for more details. +There are five `join_` functions in total, each designed to append specific information from other tables and elements in the `austraits` object. Their suffixes refer to the type of information that is joined, e.g. `join_taxa` appends taxonomic information to the `traits` dataframe. See `?join_location_coordinates` for more details. ```{r, join_} # Join taxonomic information -(data_leaf %>% join_taxonomy)$traits %>% head() +(data_leaf %>% join_taxa)$traits %>% head() # Join methodological information (data_leaf %>% join_methods)$traits %>% head() -# Join site based information -(data_leaf %>% join_sites)$traits %>% head() +# Join location coordinates +(data_leaf %>% join_location_coordinates)$traits %>% head() + +# Join information pertaining to location properties +(data_leaf %>% join_location_coordinates)$traits %>% head() # Join context information -(data_leaf %>% join_contexts)$traits %>% head() +(data_leaf %>% join_context_properties)$traits %>% head() # Alternatively users can join *all* information -(data_leaf %>% join_all)$traits %>% head() +data_leaf %>% database_create_combined_table() %>% head() ``` ## Visualising data by site -`plot_site_locations` graphically summarises where trait data was collected from and how much data is available. The legend refers to the number of neighbouring points: the warmer the colour, the more data that is available. This function only works for studies that are geo-referenced. Users must first use `join_sites` to append latitude and longitude information into the trait dataframe before plotting +`plot_site_locations` graphically summarises where trait data was collected from and how much data is available. The legend refers to the number of neighbouring points: the warmer the colour, the more data that is available. This function only works for studies that are geo-referenced. Users must first use `join_location_coordinates` to append latitude and longitude information into the trait dataframe before plotting ```{r, site_plot, fig.align = "center", fig.width=5, fig.height=5} -data_wood_dens <- data_wood_dens %>% join_sites() +data_wood_dens <- data_wood_dens %>% join_location_coordinates() plot_site_locations(data_wood_dens$traits) ``` @@ -228,13 +231,4 @@ data_wide_bound %>% separate_trait_values(., austraits$definitions) ``` -#### `summarise_trait_means` - -```{r, pivot_summarised} -data_wide_summarised <- data_falster_studies$traits %>% - summarise_trait_means() %>% - trait_pivot_wider() - -data_wide_summarised$value %>% head() -```