Skip to content

Commit

Permalink
update Eurostat env_air_gge to 2024 data
Browse files Browse the repository at this point in the history
  • Loading branch information
fbenke-pik committed Oct 28, 2024
1 parent 2af72e8 commit e8b1549
Show file tree
Hide file tree
Showing 3 changed files with 275 additions and 54 deletions.
115 changes: 66 additions & 49 deletions R/convertEurostat.R
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
#' Converts Eurostat historical emissions
#' Read Eurostat historical emissions (env_air_gge)
#'
#' @param x MAgPIE object to be converted
#' @param subtype emissions for original eurostat emissions split, MACCemi for MACC historical emissions, or
#' sectorEmi for sector specific emissions
#' @param subtype 'emissions' for original Eurostat emissions split,
#' 'MACCemi' for MACC historical emissions, or 'sectorEmi' for sector specific
#' emissions
#' @return A MAgPIE object containing the Eurostat historical emissions (MtCO2)
#' @author Renato Rodrigues
#' @examples
Expand All @@ -11,72 +12,88 @@
#' }
#'
convertEurostat <- function(x, subtype) {

switch(subtype,
"emissions" = toolCountryFill(x, fill = NA, verbosity = 2),
"sectorEmi" = convertEurostatSectorEmi(x),
"MACCemi" = convertEurostatMACCemi(x),
stop("Bad input for convertEurostat. Invalid 'subtype' argument."))
"emissions" = toolCountryFill(x, fill = NA, verbosity = 2),
"sectorEmi" = convertEurostatSectorEmi(x),
"MACCemi" = convertEurostatMACCemi(x),
stop("Bad input for convertEurostat. Invalid 'subtype' argument.")
)
}

######################################################################################
# Functions
######################################################################################
convertEurostatSectorEmi <- function(x) {
x <- toolCountryFill(x, fill = NA, verbosity = 2)
x <- toolCountryFill(x, fill = NA, verbosity = 2)
# mapping eurostat to sector emissions
mapping <- list("power" = list("energy" = c("Fuel combustion in public electricity and heat production")),
"refining" = list("energy" = c("Fuel combustion in petroleum refining")),
"solids" = list("energy" = c("Fuel combustion in manufacture of solid fuels and other energy industries", #nolint
"Other fuel combustion sectors n_e_c_")),
"extraction" = list("process" = c("Solid fuels - fugitive emissions",
"Oil, natural gas and other energy production - fugitive emissions")),
"build" = list("energy" = c("Fuel combustion in commercial and institutional sector",
"Fuel combustion by households")),
"indst" = list("energy" = c("Fuel combustion in manufacturing industries and construction"),
"process" = c("Industrial processes and product use")),
"trans" = list("energy" = c("Fuel combustion in transport")),
"bunkers" = list("energy" = c("International bunkers (memo item)")),
"agriculture" = list("energy" = c("Fuel combustion in agriculture, forestry and fishing"),
"process" = c("Agriculture")),
"waste" = list("process" = c("Waste management")),
"lulucf" = list("process" = c("Land use, land use change, and forestry (LULUCF)")),
"cdr" = list("process" = c("Transport and storage of CO2 (memo item)")),
"other" = list("energy" = c("Multilateral operations (memo item)"),
"process" = c("Other sectors")),
"indirect" = list("process" = c("Indirect CO2")))
mapping <- list(
"power" = list("energy" = c("Fuel combustion in public electricity and heat production")),
"refining" = list("energy" = c("Fuel combustion in petroleum refining")),
"solids" = list("energy" = c(
"Fuel combustion in manufacture of solid fuels and other energy industries", # nolint
"Other fuel combustion sectors n_e_c_"
)),
"extraction" = list("process" = c(
"Solid fuels - fugitive emissions",
"Oil, natural gas and other energy production - fugitive emissions"
)), # nolint
"build" = list("energy" = c(
"Fuel combustion in commercial and institutional sector",
"Fuel combustion by households"
)),
"indst" = list(
"energy" = c("Fuel combustion in manufacturing industries and construction"),
"process" = c("Industrial processes and product use")
),
"trans" = list("energy" = c("Fuel combustion in transport")),
"bunkers" = list("energy" = c("International bunkers (memo item)")),
"agriculture" = list(
"energy" = c("Fuel combustion in agriculture, forestry and fishing"),
"process" = c("Agriculture")
),
"waste" = list("process" = c("Waste management")),
"lulucf" = list("process" = c("Land use, land use change, and forestry (LULUCF)")),
"cdr" = list("process" = c("Transport and storage of CO2 (memo item)")),
"other" = list(
"energy" = c("Multilateral operations (memo item)"),
"process" = c("Other sectors")
),
"indirect" = list("process" = c("Indirect CO2"))
)

x <- mbind(lapply(names(mapping), function(var) {
mbind(lapply(names(mapping[[var]]), function(t) {
add_dimension(
add_dimension(
dimSums(x[, , mapping[[var]][[t]]], na.rm = TRUE, dim = 3.2),
dim = 3.2, add = "sector", nm = var),
dim = 3.3, add = "type", nm = t)
dim = 3.2, add = "sector", nm = var
),
dim = 3.3, add = "type", nm = t
)
}))
}))
}



convertEurostatMACCemi <- function(x) {
x <- toolCountryFill(x, fill = NA, verbosity = 2)
x <- toolCountryFill(x, fill = NA, verbosity = 2)
# mapping eurostat to MACC emissions
mapping <- list("ch4coal" = list("emi" = "CH4", "accounts" = c("Solid fuels - fugitive emissions")),
"ch4wstl" = list("emi" = "CH4", "accounts" = c("Solid waste disposal")),
"ch4wsts" = list("emi" = "CH4", "accounts" = c("Wastewater treatment and discharge")),
"ch4rice" = list("emi" = "CH4", "accounts" = c("Rice cultivation")),
"ch4animals" = list("emi" = "CH4", "accounts" = c("Enteric fermentation")),
"ch4anmlwst" = list("emi" = "CH4", "accounts" = c("Manure management")),
"ch4agwaste" = list("emi" = "CH4", "accounts" = c("Field burning of agricultural residues")),
"n2otrans" = list("emi" = "N2O", "accounts" = c("Fuel combustion in transport")),
"n2oadac" = list("emi" = "N2O", "accounts" = c("Adipic acid production")),
"n2onitac" = list("emi" = "N2O", "accounts" = c("Nitric acid production")),
"n2oagwaste" = list("emi" = "N2O", "accounts" = c("Field burning of agricultural residues")),
# or full Waste management n2O?
"n2owaste" = list("emi" = "N2O", "accounts" = c("Wastewater treatment and discharge")),
"co2cement_process" = list("emi" = "CO2", "accounts" = c("Industrial processes and product use")),
"co2luc" = list("emi" = "CO2", "accounts" = c("Land use, land use change, and forestry (LULUCF)")))
mapping <- list(
"ch4coal" = list("emi" = "CH4", "accounts" = c("Solid fuels - fugitive emissions")),
"ch4wstl" = list("emi" = "CH4", "accounts" = c("Solid waste disposal")),
"ch4wsts" = list("emi" = "CH4", "accounts" = c("Wastewater treatment and discharge")),
"ch4rice" = list("emi" = "CH4", "accounts" = c("Rice cultivation")),
"ch4animals" = list("emi" = "CH4", "accounts" = c("Enteric fermentation")),
"ch4anmlwst" = list("emi" = "CH4", "accounts" = c("Manure management")),
"ch4agwaste" = list("emi" = "CH4", "accounts" = c("Field burning of agricultural residues")),
"n2otrans" = list("emi" = "N2O", "accounts" = c("Fuel combustion in transport")),
"n2oadac" = list("emi" = "N2O", "accounts" = c("Adipic acid production")),
"n2onitac" = list("emi" = "N2O", "accounts" = c("Nitric acid production")),
"n2oagwaste" = list("emi" = "N2O", "accounts" = c("Field burning of agricultural residues")),
# or full Waste management n2O?
"n2owaste" = list("emi" = "N2O", "accounts" = c("Wastewater treatment and discharge")),
"co2cement_process" = list("emi" = "CO2", "accounts" = c("Industrial processes and product use")),
"co2luc" = list("emi" = "CO2", "accounts" = c("Land use, land use change, and forestry (LULUCF)"))
)

# other MACCs do not have a direct mapping to the eurostat data (use sector information instead)
# ch4gas + ch4oil -> extraction.process.ch4 - ch4coal #nolint
Expand Down
41 changes: 36 additions & 5 deletions R/readEurostat.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
#' Read Eurostat historical emissions
#' Read Eurostat historical emissions (env_air_gge)
#'
#' Read-in Eurostat historical emissions csv files as magclass object
#'
#' @param subtype emissions for original eurostat emissions split, MACCemi for MACC historical emissions, or
#' sectorEmi for sector specific emissions
#' @param subtype 'emissions' for original Eurostat emissions split,
#' 'MACCemi' for MACC historical emissions, or 'sectorEmi' for sector specific
#' emissions
#' @return magpie object of Eurostat historical emissions (MtCO2)
#' @author Renato Rodrigues
#' @seealso \code{\link{readSource}}
Expand All @@ -29,8 +30,8 @@ readEurostat <- function(subtype = "emissions") {
######################################################################################
# Functions
######################################################################################
readEurostatEmissions <- function() {
# Reading Eurostat historical emissions
# Reading Eurostat historical emissions from 2019
readEurostatEmissions2019 <- function() {
type <- c("GHG", "CO2", "CH4", "CH4_native", "N2O", "N2O_native", "HFC", "PFC", "HFC_PFC_NSP", "SF6", "NF3")
data <- NULL
for (t in type) {
Expand All @@ -48,3 +49,33 @@ readEurostatEmissions <- function() {
)
return(as.magpie(data, spatial = 2, temporal = 1, datacol = 5))
}

# Reading Eurostat latest historical emissions from 2024
readEurostatEmissions <- function() {

# read in GBR values from 2019 database
gbr <- readEurostatEmissions2019()["GBR",,]
gbr <- add_columns(gbr, addnm = c("y2020", "y2021", "y2022"), dim = "period", fill = NA)

df <- read.csv(file.path("2024", "env_air_gge_linear.csv")) %>%
filter(.data$unit == "MIO_T", .data$geo != "EU27_2020") %>%
select("region" = "geo", "period" = "TIME_PERIOD", "emi" = "airpol", "sector" = "src_crf", "value" = "OBS_VALUE")

df$region <- toolCountry2isocode(df$region, mapping = c("EL" = "GRC"))

x <- as.magpie(df, spatial = 1, temporal = 2, datacol = 5)

sectorMap <- toolGetMapping("EurostatCRFLabels.csv", type = "sectoral", where = "mrcommons")

airpolMap <- data.frame(
from = c("CH4", "CH4_CO2E", "CO2", "GHG", "HFC_CO2E", "HFC_PFC_NSP_CO2E",
"N2O", "N2O_CO2E", "NF3_CO2E", "PFC_CO2E", "SF6_CO2E"),
to = c("CH4_native", "CH4", "CO2", "GHG", "HFC", "HFC_PFC_NSP",
"N2O_native", "N2O", "NF3", "PFC", "SF6")
)
x <- toolAggregate(x, dim = 3.1, rel = airpolMap, from = "from", to = "to")
x <- toolAggregate(x, dim = 3.2, rel = sectorMap, from = "crf", to = "label")

return(mbind(x, gbr))

}
173 changes: 173 additions & 0 deletions inst/extdata/sectoral/EurostatCRFLabels.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,173 @@
crf;label
TOTXMEMO;Total (excluding memo items)
TOTXMEMONIA;Total (excluding memo items, including international aviation)
TOTX4_MEMO;Total (excluding LULUCF and memo items)
TOTX4_MEMONIA;Total (excluding LULUCF and memo items, including international aviation)
TOTX4_MEMONIT;Total (excluding LULUCF and memo items, including international transport)
TOTXMEMONIT;Total (excluding memo items, including international transport)
CRF1;Energy
CRF1A;Fuel combustion - sectoral approach
CRF1A1;Fuel combustion in energy industries
CRF1A1A;Fuel combustion in public electricity and heat production
CRF1A1B;Fuel combustion in petroleum refining
CRF1A1C;Fuel combustion in manufacture of solid fuels and other energy industries
CRF1A2;Fuel combustion in manufacturing industries and construction
CRF1A2A;Fuel combustion in manufacture of iron and steel
CRF1A2B;Fuel combustion in manufacture of non-ferrous metals
CRF1A2C;Fuel combustion in manufacture of chemicals
CRF1A2D;Fuel combustion in manufacture of pulp, paper and printing
CRF1A2E;Fuel combustion in manufacture of food, beverages and tobacco
CRF1A2F;Fuel combustion in manufacture of non-metallic mineral products
CRF1A2G;Fuel combustion in other manufacturing industries and construction
CRF1A3;Fuel combustion in transport
CRF1A3A;Fuel combustion in domestic aviation
CRF1A3B;Fuel combustion in road transport
CRF1A3B1;Fuel combustion in cars
CRF1A3B2;Fuel combustion in light duty trucks
CRF1A3B3;Fuel combustion in heavy duty trucks and buses
CRF1A3B4;Fuel combustion in motorcycles
CRF1A3B5;Fuel combustion in other road transportation
CRF1A3C;Fuel combustion in railways
CRF1A3D;Fuel combustion in domestic navigation
CRF1A3E;Fuel combustion in other transport
CRF1A4;Other fuel combustion sectors
CRF1A4A;Fuel combustion in commercial and institutional sector
CRF1A4B;Fuel combustion by households
CRF1A4C;Fuel combustion in agriculture, forestry and fishing
CRF1A5;Other fuel combustion sectors n_e_c_
CRF1A5A;Stationary fuel combustion sectors n_e_c_
CRF1A5B;Mobile fuel combustion sectors n_e_c_
CRF1B;Fuels - fugitive emissions
CRF1B1;Solid fuels - fugitive emissions
CRF1B2;Oil, natural gas and other energy production - fugitive emissions
CRF1C;Transport and storage of CO2 (memo item)
CRF1D1;International bunkers (memo item)
CRF1D1A;International aviation (memo item)
CRF1D1B;International navigation (memo item)
CRF1D2;Multilateral operations (memo item)
CRF1D3;Biomass - CO2 emissions (memo item)
CRF2;Industrial processes and product use
CRF2A;Mineral industry
CRF2A1;Cement production
CRF2A2;Lime production
CRF2A3;Glass production
CRF2A4;Other process uses of carbonates
CRF2B;Chemical industry
CRF2B1;Ammonia production
CRF2B2;Nitric acid production
CRF2B3;Adipic acid production
CRF2B4;Caprolactam, glyoxal and glyoxylic acid production
CRF2B5;Carbide production
CRF2B6;Titanium dioxide production
CRF2B7;Soda ash production
CRF2B8;Petrochemical and carbon black production
CRF2B9;Fluorochemical production
CRF2B10;Other chemical industry
CRF2C;Metal industry
CRF2C1;Iron and steel production
CRF2C2;Ferroalloys production
CRF2C3;Aluminium production
CRF2C4;Magnesium production
CRF2C5;Lead production
CRF2C6;Zinc production
CRF2C7;Other metal industry
CRF2D;Non-energy products from fuels and solvent use
CRF2D1;Lubricant use
CRF2D2;Paraffin wax use
CRF2D3;Other non-energy product use
CRF2E;Electronics industry
CRF2E1;Integrated circuit or semiconductor production
CRF2E2;TFT flat panel display production
CRF2E3;Photovoltaic
CRF2E4;Heat transfer fluid
CRF2E5;Other electronics industry
CRF2F;Product uses as substitutes for ozone depleting substances
CRF2F1;Refrigeration and air conditioning
CRF2F2;Foam blowing agent use
CRF2F3;Fire protection
CRF2F4;Aerosol use
CRF2F5;Solvent use
CRF2F6;Other applications of substitutes for ozone depleting substances
CRF2G;Other product manufacture and use
CRF2H;Other industrial process and product use
CRF3;Agriculture
CRF31;Livestock
CRF3A;Enteric fermentation
CRF3A1;Enteric fermentation of cattle
CRF3A2;Enteric fermentation of sheep
CRF3A3;Enteric fermentation of swine
CRF3A4;Enteric fermentation of other livestock
CRF3B;Manure management
CRF3B1;Cattle manure management
CRF3B2;Sheep manure management
CRF3B3;Swine manure management
CRF3B4;Other livestock manure management
CRF3B5;Manure management - indirect N2O emissions
CRF3C;Rice cultivation
CRF3C1;Irrigated rice cultivation
CRF3C2;Rainfed rice cultivation
CRF3C3;Deep water rice cultivation
CRF3C4;Other rice cultivation
CRF3D;Managed agricultural soils
CRF3D1;Managed agricultural soils - direct N2O emissions
CRF3D2;Managed agricultural soils - indirect N2O emissions
CRF3E;Prescribed burning of savannas
CRF3F;Field burning of agricultural residues
CRF3F1;Field burning of cereals residues
CRF3F2;Field burning of pulses residues
CRF3F3;Field burning of tubers and roots residues
CRF3F4;Field burning of sugar cane residues
CRF3F5;Field burning of other agricultural residues
CRF3G;Liming
CRF3H;Urea application
CRF3I;Other carbon-containing fertilizers
CRF3J;Other agriculture
CRF4;Land use, land use change, and forestry (LULUCF)
CRF4A;Forest land
CRF4A0;Drainage and rewetting and other management of organic and mineral soils related to forest land - emissions and removals
CRF4A1;Unconverted forest land
CRF4A2;Land converted to forest land
CRF4B;Cropland
CRF4B0;Drainage and rewetting and other management of organic and mineral soils related to cropland - emissions and removals
CRF4B1;Unconverted cropland
CRF4B2;Land converted to cropland
CRF4C;Grassland
CRF4C0;Drainage and rewetting and other management of organic and mineral soils related to grassland - emissions and removals
CRF4C1;Unconverted grassland
CRF4C2;Land converted to grassland
CRF4D;Wetlands
CRF4D0;Drainage and rewetting and other management of organic and mineral soils related to wetlands - emissions and removals
CRF4D1;Unconverted wetlands
CRF4D2;Land converted to wetlands
CRF4E;Settlements
CRF4E0;Biomass burning in settlements
CRF4E1;Unconverted settlements
CRF4E2;Land converted to settlements
CRF4F;Other land
CRF4F2;Land converted to other land
CRF4F3;Nitrogen mineralization and immobilization in other land - direct N2O emissions
CRF4F4;Biomass burning on other land
CRF4G;Harvested wood products
CRF4H;Other land use, land use change, and forestry
CRF4Z;Managed soils - indirect N2O emissions
CRF5;Waste management
CRF5A;Solid waste disposal
CRF5A1;Managed waste disposal sites
CRF5A2;Unmanaged waste disposal sites
CRF5A3;Uncategorized waste disposal sites
CRF5B;Biological treatment of solid waste
CRF5B1;Waste composting
CRF5B2;Anaerobic digestion at biogas facilities
CRF5C;Incineration and open burning of waste
CRF5C1;Waste incineration
CRF5C2;Open burning of waste
CRF5D;Wastewater treatment and discharge
CRF5D1;Domestic wastewater
CRF5D2;Industrial wastewater
CRF5D3;Other wastewater
CRF5E;Other disposal
CRF5F1;Long-term storage of carbon in waste disposal sites
CRF5F2;Annual change in total long-term carbon storage
CRF5F3;Annual change in total long-term carbon storage in harvested wood products HWP waste
CRF6;Other sectors
CRF_INDCO2;Indirect CO2

0 comments on commit e8b1549

Please sign in to comment.