Skip to content
Snippets Groups Projects
Commit 0bd90e6c authored by Franssen, Wietse's avatar Franssen, Wietse
Browse files

updated some functions

parent 0d096c24
No related branches found
No related tags found
No related merge requests found
......@@ -4,10 +4,25 @@ R2Netcdf <- function(outFile, rData) {
## CREATE NETCDF
FillValue <- 1e20
## Check dimensions
dimensions<-attributes(rData$Data)$dimensions
## Check if 'member', or 4th dimension exist
nDims <- length(dim(rData$Data))
if (nDims > 3) {
if (!'member' %in% dimensions){
stop("dimension 'member' not defined!")
}
}
## Define dimensions
dimX <- ncdim_def("lon", "degrees_east", rData$xyCoords$x)
dimY <- ncdim_def("lat", "degrees_north",rData$xyCoords$y)
if (nDims > 3) {
dimZ <- ncdim_def("member", "layer",1:dim(rData$Data)[which(dimensions == "member")])
#dimZ <- ncdim_def(name = "layer",units = '',vals = 1:dim(rData$Data)[which(dimensions == "member")], create_dimvar = FALSE)
}
timeString<-format(strptime(rData$Dates$start[1], format = "%Y-%m-%d", tz = "GMT"),format="%Y-%m-%d %T")
timeArray<-as.double(difftime(rData$Dates$start,rData$Dates$start[1], units = c("days")))
dimT <- ncdim_def("time", paste0("days since ",timeString), timeArray, unlim = FALSE)
......@@ -18,17 +33,27 @@ R2Netcdf <- function(outFile, rData) {
units<-""
}
data <- ncvar_def(name=rData$Variable$varName, units=units, dim=list(dimX,dimY,dimT), missval=FillValue, prec="float",chunksizes = c(length(rData$xyCoords$x),length(rData$xyCoords$y),1), compression=4)
if (nDims > 3) {
data <- ncvar_def(name=rData$Variable$varName, units=units, dim=list(dimX,dimY,dimZ,dimT), missval=FillValue, prec="float",chunksizes = c(length(rData$xyCoords$x),length(rData$xyCoords$y),1,1), compression=4)
} else {
data <- ncvar_def(name=rData$Variable$varName, units=units, dim=list(dimX,dimY,dimT), missval=FillValue, prec="float",chunksizes = c(length(rData$xyCoords$x),length(rData$xyCoords$y),1), compression=4)
}
## SAVE AS NC-DATA
print(paste0("Writing: ", outFile))
ncid <- nc_create(outFile, list(data))
dimensions<-attributes(rData$Data)$dimensions
ncvar_put(ncid, data, aperm(rData$Data, c(which(dimensions == "lon"),
which(dimensions == "lat"),
which(dimensions == "time"))))
if (nDims > 3) {
ncvar_put(ncid, data, aperm(rData$Data, c(which(dimensions == "lon"),
which(dimensions == "lat"),
which(dimensions == "time"),
which(dimensions == "member"))))
} else {
ncvar_put(ncid, data, aperm(rData$Data, c(which(dimensions == "lon"),
which(dimensions == "lat"),
which(dimensions == "time"))))
}
ncatt_put( ncid, "lon", "standard_name", "longitude")
ncatt_put( ncid, "lon", "long_name", "Longitude")
......@@ -45,7 +70,10 @@ R2Netcdf <- function(outFile, rData) {
## Global Attributes
if ('InitializationDates' %in% names(rData)) ncatt_put( ncid, 0, "InitializationDates", rData$InitializationDates)
if ('Members' %in% names(rData)) ncatt_put( ncid, 0, "Members", rData$Members)
if ('Members' %in% names(rData)) {
membernames<-paste(rData$Members, sep = ' ', collapse = ' ')
ncatt_put( ncid, 0, "Members", membernames)
}
## Get all global attributes from rData and put them in the NetCDF file
attributeList<-attributes(rData)
......@@ -54,7 +82,7 @@ R2Netcdf <- function(outFile, rData) {
ncatt_put( ncid, 0, names(attributeList)[iAttribute], as.character(attributeList[iAttribute[]]))
}
ncatt_put( ncid, 0, "NetcdfCreatationDate", as.character(Sys.Date()))
length(attributeList)
## Close Netcdf file
nc_close(ncid)
......
rm(list=ls())
source(file = "./functionsGeneral.R")
reformat2Bias<-function(members, initYears, initMonth, varName, locName, iPath = "/home/wietse/TODO/output/") {
reformat2Bias<-function(members, initYears, initMonth, varName, locName,
iFile = "./forcing_seas15_GHA_ref__E<MEMBERS>_<YEARS>_01.Rdata") {
sYear<-initYears[1]
eYear<-initYears[length(initYears)]
nYears<-length(initYears)
......@@ -22,13 +23,12 @@ reformat2Bias<-function(members, initYears, initMonth, varName, locName, iPath =
for (initYear in initYears) {
indexesYearsLeadMonths<-indexesForYearsPerLeadMonth(sYear,eYear,initMonth)
nameFileR <- sprintf(paste0(iPath,"/%s_forcing_seas15_%s_ref__E%02d_%4d_%02d.Rdata"),
varName,
locName,
iMember,
initYear,
initMonth)
print(paste0("Opening: ", nameFileR))
nameFileR <- iFile
strYear <- sprintf("%4d",initYear)
strMember <- sprintf("%02d",iMember)
nameFileR <-gsub("<MEMBERS>", strMember, nameFileR)
nameFileR <-gsub("<YEARS>", strYear, nameFileR)
print(paste0("Opening2 ", nameFileR))
load(nameFileR)
if (!allocatedOutputArray) {
......@@ -50,6 +50,7 @@ reformat2Bias<-function(members, initYears, initMonth, varName, locName, iPath =
finalList[[iLM]]$Dates$start<-character(length=totalDays)
finalList[[iLM]]$Dates$end<-character(length=totalDays)
attr(finalList[[iLM]]$Data,"dimensions") <- c("member","time","lat","lon")
attr(finalList[[iLM]],"LeadMonth") <- iLM-1
}
names(finalList)<-listNames
allocatedOutputArray<-TRUE
......
......@@ -3,19 +3,18 @@ rm(list=ls())
source(file = "./functionReformat.R")
source(file = "./functionR2Netcdf.R")
iPath<-"/home/wietse/TODO/tttas/"
initYears<-c(1981:1982)
#initYears<-c(1981:2010)
# initYears<-c(1981:2010)
members<-c(1:2)
#members<-c(1:15)
# members<-c(1:15)
varName<-"tas"
locName<-"GHA"
#locName<-"EU"
initMonth<-1
rData<-reformat2Bias(members, initYears, initMonth, varName, locName, iPath = iPath)
iFile = paste0("/home/wietse/TODO/tttas/",varName,"_forcing_seas15_",locName, "_ref__E<MEMBERS>_<YEARS>_01.Rdata")
rData <- reformat2Bias(members, initYears, initMonth, varName, locName, iFile = iFile)
# outF<-("/home/wietse/TODO/SCRIPTS/fileTest2.nc4")
# R2Netcdf(outF, rData$LeadMonth_1)
outF<-("/home/wietse/TODO/SCRIPTS/test.nc4")
R2Netcdf(outF, rData$LeadMonth_3)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment